Ignore:
Timestamp:
03/15/18 14:18:24 (6 years ago)
Author:
aquiquet
Message:

Grisli-iloveclim branch merged to trunk at revision 185

Location:
branches/iLoveclim
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/iLoveclim

  • branches/iLoveclim/SOURCES/furst_schoof_mod.f90

    r123 r187  
    1414real,dimension(nx,ny) :: back_force_y 
    1515real, parameter :: m_weert = 1.0 ! afq: is this defined elsewhere in the model??? 
     16real, parameter :: inv_mweert = 1./m_weert 
    1617 
    1718contains 
     
    5455  integer,dimension(nx,ny) :: countx, county   ! how often do we modify ux/uy 
    5556  real :: phi_prescr 
    56   real :: archim 
    5757  real :: toutpetit = 1e-6 
    5858  real :: denom, prodscal 
     59 
     60  real :: bfx, bfy 
    5961 
    6062  !debug 
     
    102104              xpos_tab(i,j)=xpos 
    103105              Hglx_tab(i,j)=Hgl 
    104  
     106               
     107              ! afq: the back force is on the staggered grid, the GL can be either West or East to this point. 
     108              if (xpos .lt. -dx/2.) then 
     109                 bfx = back_force_x(i,j) 
     110              else 
     111                 bfx = back_force_x(i+1,j) 
     112              endif 
    105113              if (gr_select.eq.1) then ! flux de Tsai 
    106                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_x(i-1,j),phi_prescr) 
     114                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),bfx,phi_prescr) 
    107115              else if (gr_select.eq.2) then ! flux de Schoof 
    108116                 ! afq: the dragging coef. is on the staggered grid, the GL can be either West or East to this point. 
     
    112120                    frot_coef = betamx(i+1,j) 
    113121                 endif 
    114                  call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,back_force_x(i-1,j),phi_prescr) 
     122                 call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,bfx,phi_prescr) 
    115123              else 
    116124                 print*,'ATTENTION FLUX AUTRE QUE TSAI OU SCHOOF NON IMPLEMENTE' 
     
    190198              xpos_tab(i,j)=xpos 
    191199              Hglx_tab(i,j)=Hgl 
     200               
     201              ! afq: the back force is on the staggered grid, the GL can be either West or East to this point. 
     202              if (xpos .lt. dx/2.) then 
     203                 bfx = back_force_x(i,j) 
     204              else 
     205                 bfx = back_force_x(i+1,j) 
     206              endif 
    192207              if (gr_select.eq.1) then ! flux de Tsai 
    193                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_x(i+1,j),phi_prescr) 
     208                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),bfx,phi_prescr) 
    194209              else if (gr_select.eq.2) then ! flux de Schoof 
    195210                 ! afq: the dragging coef. is on the staggered grid, the GL can be either West or East to this point. 
    196                  if (xpos .lt. -dx/2.) then 
     211                 if (xpos .lt. dx/2.) then 
    197212                    frot_coef = betamx(i,j) 
    198213                 else 
    199214                    frot_coef = betamx(i+1,j) 
    200215                 endif 
    201                  call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,back_force_x(i+1,j),phi_prescr) 
     216                 call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,bfx,phi_prescr) 
    202217              else 
    203218                 print*,'ATTENTION FLUX AUTRE QUE TSAI OU SCHOOF NON IMPLEMENTE' 
     
    205220              endif 
    206221              phi_prescr_tabx(i,j)=phi_prescr 
    207               if (xpos .lt. -dx/2.) then  !  GL a west du i staggered,                          o centre, x stag 
     222              if (xpos .lt. dx/2.) then  !  GL a west du i staggered,                          o centre, x stag 
    208223 
    209224                 !  grille    ! .....x......o......x......o......x......O..G...x......o......x......o 
     
    274289              ypos_tab(i,j)=ypos 
    275290              Hgly_tab(i,j)=Hgl 
     291               
     292              ! afq: the back force is on the staggered grid, the GL can be either South or North to this point. 
     293              if (ypos .lt. -dy/2.) then 
     294                 bfy = back_force_y(i,j) 
     295              else 
     296                 bfy = back_force_y(i,j+1) 
     297              endif 
    276298              if (gr_select.eq.1) then ! flux de Tsai 
    277                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_y(i,j-1),phi_prescr) 
     299                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),bfy,phi_prescr) 
    278300              else if (gr_select.eq.2) then ! flux de Schoof 
    279301                 ! afq: the dragging coef. is on the staggered grid, the GL can be either South or North to this point. 
     
    283305                    frot_coef = betamy(i,j+1) 
    284306                 endif 
    285                  call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,back_force_y(i,j-1),phi_prescr) 
     307                 call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,bfy,phi_prescr) 
    286308              else 
    287309                 print*,'ATTENTION FLUX AUTRE QUE TSAI OU SCHOOF NON IMPLEMENTE' 
     
    355377              ypos_tab(i,j)=ypos 
    356378              Hgly_tab(i,j)=Hgl 
     379               
     380              ! afq: the back force is on the staggered grid, the GL can be either South or North to this point. 
     381              if (ypos .lt. dy/2.) then 
     382                 bfy = back_force_y(i,j) 
     383              else 
     384                 bfy = back_force_y(i,j+1) 
     385              endif 
    357386              if (gr_select.eq.1) then ! flux de Tsai 
    358                  call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),back_force_y(i,j+1),phi_prescr) 
     387                 call flux_Tsai4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),bfy,phi_prescr) 
    359388              else if (gr_select.eq.2) then ! flux de Schoof 
    360389                 ! afq: the dragging coef. is on the staggered grid, the GL can be either South or North to this point. 
    361                  if (ypos .lt. -dy/2.) then 
     390                 if (ypos .lt. dy/2.) then 
    362391                    frot_coef = betamy(i,j) 
    363392                 else 
    364393                    frot_coef = betamy(i,j+1) 
    365394                 endif 
    366                  call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,back_force_y(i,j+1),phi_prescr) 
     395                 call flux_Schoof4Schoof (Hgl,Abar(i,j),frot_coef,alpha_flot,glen(1),m_weert,bfy,phi_prescr) 
    367396              else 
    368397                 print*,'ATTENTION FLUX AUTRE QUE TSAI OU SCHOOF NON IMPLEMENTE' 
     
    370399              endif 
    371400              phi_prescr_taby(i,j)=phi_prescr 
    372               if (ypos .lt. -dy/2.) then  !  GL au sud du j staggered,                          o centre, x stag 
     401              if (ypos .lt. dy/2.) then  !  GL au sud du j staggered,                          o centre, x stag 
    373402 
    374403                 !  grille    ! .....x......o......x......o......x......O..G...x......o......x......o 
     
    471500!!$     enddo 
    472501!!$  enddo 
     502 
     503  debug_3D(:,:,66) = phi_prescr_tabx(:,:) 
     504  debug_3D(:,:,67) = phi_prescr_taby(:,:) 
     505   
    473506end subroutine interpol_glflux 
    474507   
     
    561594! afq: in standard GRISLI (19/05/17), tob= -beta ub => m_weert = 1 and C_frot = beta 
    562595 
    563  
    564 phi_schoof = (((A_mean * rog**(n_glen+1) * (1 - alpha)**n_glen) / (4**n_glen *C_frot)) **(1./(1.+1./m_weert)))*back_force_coef 
    565 phi_schoof = phi_schoof * Hgl**((n_glen+3.+1/m_weert)/(1.+1./m_weert)) 
     596!phi_schoof = (((A_mean * rog**(n_glen+1) * (1 - alpha)**n_glen) / (4**n_glen *C_frot)) **(1./(1.+1./m_weert)))*back_force_coef**(n_glen/(1+1./m_weert)) 
     597!phi_schoof = phi_schoof * Hgl**((n_glen+3.+1/m_weert)/(1.+1./m_weert)) 
     598phi_schoof = (((A_mean * rog**(n_glen+1.) * (1. - alpha)**n_glen) / (4.**n_glen*C_frot)) **(1./(1.+inv_mweert)))*back_force_coef**(n_glen/(1.+inv_mweert)) 
     599phi_schoof = phi_schoof * Hgl**((n_glen+3.+inv_mweert)/(1.+inv_mweert)) 
    566600 
    567601 
     
    590624 
    591625 
    592 phi_Tsai = Q0 * ((8 * A_mean * rog**(n_glen) * (1 - alpha)**(n_glen-1.)) / (4**n_glen *f_frot))*back_force_coef 
    593 phi_Tsai = phi_Tsai * Hgl**(n_glen+2) 
     626phi_Tsai = Q0 * ((8. * A_mean * rog**(n_glen) * (1. - alpha)**(n_glen-1.)) / (4.**n_glen *f_frot))*back_force_coef**(n_glen-1.) 
     627phi_Tsai = phi_Tsai * Hgl**(n_glen+2.) 
    594628 
    595629end subroutine flux_Tsai4Schoof 
Note: See TracChangeset for help on using the changeset viewer.