Ignore:
Timestamp:
01/30/21 10:50:17 (3 years ago)
Author:
aquiquet
Message:

Coulomb friction law: possibility to tune the drag coefficient given a sediment thickness map (or relaxed bedrock elevation)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/dragging_coulomb_friction_mod.f90

    r333 r334  
    3838!    - number of iterations (as it is non-linear) 
    3939!    - betamin and betamax 
     40! 
     41! I also add the possibility to tune locally the cf coefficient to account for 
     42! the presence of sediments (could also be Bsoc_relax<0 for Antarctica) 
    4043!______________________________________________________________________________ 
    4144 
     
    5154real :: m_nolin   !  Schoof non-linear exponent 
    5255real :: q_nolin   !  q=1/m 
     56 
     57real, dimension(nx,ny) :: coef_sedim_mx, coef_sedim_my ! in case we use sediments 
    5358 
    5459real, dimension(nx,ny) :: Vcol_x           !< uniquement pour compatibilite avec spinup cat 
     
    6974use runparam,     only: itracebug 
    7075 
     76use interface_input  !for sediments 
     77use io_netcdf_grisli !for sediments 
     78 
    7179implicit none 
    7280 
    73 namelist/drag_coulomb_friction/cf,m_nolin,niter_nolin,betamax,betamin 
     81logical :: bool_sedim              ! sediments: yes or no 
     82real :: seuil_sedim                ! sediment thickness threshold for drag reduction 
     83real :: coef_sedim                 ! drag reduction factor 
     84real,dimension(nx,ny) :: h_sedim   ! sediment thickness (or rebounded bedrock) 
     85real,dimension(nx,ny) :: h_sedimmx,h_sedimmy   ! temporary arrays 
     86character(len=150) :: file_sedim   ! file for sediment thickness for HN or rebounded bsoc for Antar 
     87character(len=150) :: file_ncdf    ! fichier netcdf issue des fichiers .dat 
     88integer i,j 
     89 
     90namelist/drag_coulomb_friction/cf,m_nolin,niter_nolin,betamax,betamin,bool_sedim,file_sedim,seuil_sedim,coef_sedim 
    7491 
    7592if (itracebug.eq.1)  call tracebug(' dragging avec neff et slope') 
     
    93110write(num_rep_42,*) 'betamax               = ', betamax 
    94111write(num_rep_42,*) 'betamin               = ', betamin 
     112write(num_rep_42,*) 'bool_sedim            = ', bool_sedim 
     113write(num_rep_42,'(A,A,A)') 'file_sedim    = "',trim(file_sedim),'"' 
     114write(num_rep_42,*) 'seuil_sedim           = ', seuil_sedim 
     115write(num_rep_42,*) 'coef_sedim            = ', coef_sedim 
    95116write(num_rep_42,*)'/'                             
    96117write(num_rep_42,428) '! cf: a friction coefficient (to be tuned)' 
     
    98119write(num_rep_42,428) '!          m_nolin=1/q in Pattyn TC 2017, q in [0:1]' 
    99120write(num_rep_42,428) '! niter_nolin: number of iterations to solve the non-linearity (expensive!)' 
     121write(num_rep_42,428) '! Possibility to add sediment tuning of cf, if false, the file is not read' 
     122write(num_rep_42,428) '! If sediments: where h_sedim > seuil_sedim, beta*coef_sedim' 
    100123 
    101124inv_beta=0 
     
    116139else 
    117140   q_nolin = 1 / m_nolin 
     141endif 
     142 
     143if (bool_sedim) then 
     144    
     145   file_sedim=trim(dirnameinp)//trim(file_sedim) 
     146   call lect_input(1,'h_sedim',1,h_sedim(:,:),file_sedim,file_ncdf) 
     147 
     148   h_sedimmx(1,:)=h_sedim(1,:) 
     149   h_sedimmy(:,1)=h_sedim(:,1) 
     150   do i=2,nx 
     151      h_sedimmx(i,:)=(h_sedim(i-1,:)+h_sedim(i,:))/2. 
     152   enddo 
     153   do j=2,ny 
     154      h_sedimmy(:,j)=(h_sedim(:,j-1)+h_sedim(:,j))/2. 
     155   enddo 
     156 
     157   where (h_sedimmx(:,:).gt.seuil_sedim) 
     158      coef_sedim_mx(:,:) = coef_sedim 
     159   elsewhere 
     160      coef_sedim_mx(:,:) = 1. 
     161   endwhere 
     162   where (h_sedimmy(:,:).gt.seuil_sedim) 
     163      coef_sedim_my(:,:) = coef_sedim 
     164   elsewhere 
     165      coef_sedim_my(:,:) = 1. 
     166   endwhere 
     167 
     168else 
     169    
     170   coef_sedim_mx(:,:) = 1. 
     171   coef_sedim_my(:,:) = 1. 
     172 
    118173endif 
    119174 
     
    179234!$OMP WORKSHARE 
    180235 
    181 tauc_mx(:,:)= cf*neffmx(:,:) 
    182 tauc_my(:,:)= cf*neffmy(:,:) 
     236tauc_mx(:,:)= cf*neffmx(:,:)*coef_sedim_mx(:,:) 
     237tauc_my(:,:)= cf*neffmy(:,:)*coef_sedim_my(:,:) 
    183238 
    184239where (abs(ux(:,:,nz)).gt.1) 
Note: See TracChangeset for help on using the changeset viewer.