Ignore:
Timestamp:
02/09/24 17:08:19 (5 months ago)
Author:
aquiquet
Message:

Cleaning branch: some routines with explicit arguments in New-remplimat

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/GRISLIv3/SOURCES/New-remplimat/diagno-L2_mod.f90

    r481 r482  
    1616real, dimension(nx,ny) :: uyb1ramollo 
    1717real, dimension(nx,ny) :: pvi_keep 
    18  
    19 !cdc transfere dans module3d pour compatibilite avec furst_schoof_mod 
    20 !cdc  integer, dimension(nx,ny) :: imx_diag 
    21 !cdc  integer, dimension(nx,ny) :: imy_diag 
    2218 
    2319integer :: nneigh=max(int(400000./dx),1) !nb. points around the grline kept for back force comp. in case we reduce the extent 
     
    151147!$OMP END WORKSHARE 
    152148!$OMP END PARALLEL 
    153   ! avec couplage thermomecanique 
    154 !  write(166,*) ' apres call calc_pvi',itour_pvi 
    155149 
    156150else 
     
    158152end if 
    159153 
    160   call imx_imy_nx_ny         ! pour rempli_L2 : calcule les masques imx et imy qui  
     154  call imx_imy_nx_ny(imx_diag,imy_diag,flgzmx,flgzmy)         ! pour rempli_L2 : calcule les masques imx et imy qui  
    161155 
    162156  diagno_grline=sum(gr_line(2:(nx-1),2:(ny-1))) 
    163157  if ((Schoof.ge.1).and.(diagno_grline.gt.0)) then 
    164        call imx_imy_nx_ny_reduce(1) !afq: provides imx_reduce and imy_reduce 
     158       call imx_imy_nx_ny_reduce(1,flot,imx_diag,imy_diag,gr_line) !afq: provides imx_reduce and imy_reduce 
    165159  endif 
    166  
    167 !cdc debug Schoof !!!!!!!!!!!!   
    168 !~   do j=1,ny 
    169 !~              do i=1,nx 
    170 !~                      write(578,*) uxbar(i,j) 
    171 !~                      write(579,*) uybar(i,j) 
    172 !~              enddo 
    173 !~      enddo    
    174    
    175   !if (Schoof.eq.1.and.nt.GT.15000) then ! flux grounding line Schoof 
    176 ! afq -- below:  if (Schoof.eq.1) then ! flux grounding line Schoof 
    177 ! afq -- below:     call interpol_glflux ! calcul flux GL + interpolation sur voisins 
    178 ! afq -- below:  endif 
    179  
    180 !~       do j=1,ny 
    181 !~              do i=1,nx 
    182 !~                      write(588,*) uxbar(i,j) 
    183 !~                      write(589,*) uybar(i,j) 
    184 !~              enddo 
    185 !~      enddo    
    186 !~      print*,'ecriteure termineee !!!!!!' 
    187 !~      read(*,*) 
    188160 
    189161  ! donnent les cas de conditions aux limites 
     
    202174  nyd1=1 
    203175  nyd2=ny 
    204  
    205   !call rempli_L2(1,nx,1,ny,uxbar,uybar,uxb1,uyb1,imx_diag,imy_diag,ifail_diagno)     
    206   !nxd1=15 
    207   !nxd2=19 
    208   !nyd1=30 
    209   !nyd2=34 
    210  
    211   !nxd1=35 
    212   !nxd2=60 
    213   !nyd1=35 
    214   !nyd2=60 
    215  
    216176        
    217   !if (Schoof.eq.1.and.nt.GT.15000) then ! flux grounding line Schoof avec calcul de la back force par shelf ramollo 
    218177  if ((Schoof.ge.1).and.(diagno_grline.gt.0)) then ! flux grounding line Schoof avec calcul de la back force par shelf ramollo 
    219178 
     
    224183    pvi_keep(:,:)=pvi(:,:)        
    225184    where (flot(:,:).and.H(:,:).GT.2.) 
    226 !       pvi(:,:)=1.e5     
    227185       pvi(:,:)=pvimin 
    228186    endwhere 
     
    250208 
    251209    if (ifail_diagno_ramollo.gt.0) then 
    252 !       write(6,*) ' Probleme resolution systeme L2. ramollo ifail=',ifail_diagno_ramollo 
    253 !       STOP 
    254210       write(*,*) ' Probleme resolution systeme L2. ramollo ifail=',ifail_diagno_ramollo 
    255211       write(*,*) '          ... we go on anyway!' 
    256212    endif 
    257 !~   do j=1,ny 
    258 !~              do i=1,nx 
    259 !~                if (sqrt(uxb1(i,j)**2+ uyb1(i,j)**2).gt.0..and..not.flot(i,j)) then 
    260 !~                              write(1034,*) sqrt(uxb1(i,j)**2+ uyb1(i,j)**2) / sqrt(uxb1ramollo(i,j)**2 + uyb1ramollo(i,j)**2) 
    261 !~                else 
    262 !~                              write(1034,*) 1. 
    263 !~                      endif 
    264 !~              enddo            
    265 !~      enddo 
    266  
    267 !~   print*,'apres calcul rempli_L2' 
    268 !~   read(*,*) 
    269213     
    270214    call interpol_glflux ! calcul flux GL + interpolation sur voisins 
     
    503447debug_3D(:,:,27)=pvi(:,:) 
    504448!$OMP END WORKSHARE 
    505 ! attention run 35 
    506 !--------------------  
    507 !!$if (time.gt.10.) then 
    508 !!$   where (flot(:,:)) 
    509 !!$      pvi(:,:)=pvimin 
    510 !!$   end where 
    511 !!$end if 
    512449 
    513450!  calcul de la viscosite integree au milieu des mailles (pvm) 
     
    528465!------------------------------------------------------------------ 
    529466 
    530 subroutine imx_imy_nx_ny 
    531  
    532 use module3d_phy, only: imx_diag,imy_diag,flgzmx,flgzmy  
    533           
     467subroutine imx_imy_nx_ny(imx_diagl,imy_diagl,flgzmxl,flgzmyl) 
     468 
    534469implicit none 
     470 
     471logical,dimension(:,:), intent(in)    :: flgzmxl,flgzmyl 
     472integer,dimension(:,:), intent(inout) :: imx_diagl,imy_diagl 
    535473 
    536474! definition des masques 
     
    555493!$OMP PARALLEL 
    556494!$OMP WORKSHARE 
    557 imx_diag(:,:)=0 
    558 imy_diag(:,:)=0 
     495imx_diagl(:,:)=0 
     496imy_diagl(:,:)=0 
    559497 
    560498! a l'interieur du domaine 
    561499!------------------------- 
    562500 
    563 where (flgzmx(:,:)) 
    564    imx_diag(:,:)=2             ! shelf ou stream         
     501where (flgzmxl(:,:)) 
     502   imx_diagl(:,:)=2             ! shelf ou stream         
    565503elsewhere 
    566    imx_diag(:,:)=1             ! vitesse imposee 
     504   imx_diagl(:,:)=1             ! vitesse imposee 
    567505end where 
    568506 
    569 where (flgzmy(:,:))       
    570    imy_diag(:,:)=2             ! shelf ou stream 
     507where (flgzmyl(:,:))       
     508   imy_diagl(:,:)=2             ! shelf ou stream 
    571509elsewhere 
    572    imy_diag(:,:)=1             ! vitesse imposee 
     510   imy_diagl(:,:)=1             ! vitesse imposee 
    573511end where 
    574512 
    575513! bord sud  
    576 imx_diag(:,1)=-1 
    577 imy_diag(:,2)=-1 
     514imx_diagl(:,1)=-1 
     515imy_diagl(:,2)=-1 
    578516 
    579517! bord nord 
    580 imx_diag(:,ny)=-3 
    581 imy_diag(:,ny)=-3 
     518imx_diagl(:,ny)=-3 
     519imy_diagl(:,ny)=-3 
    582520 
    583521! bord Est 
    584 imx_diag(1,:)=0    ! hors domaine a cause des mailles alternees 
    585 imx_diag(2,:)=-4 
    586 imy_diag(1,:)=-4 
     522imx_diagl(1,:)=0    ! hors domaine a cause des mailles alternees 
     523imx_diagl(2,:)=-4 
     524imy_diagl(1,:)=-4 
    587525 
    588526! bord West 
    589 imx_diag(nx,:)=-2 
    590 imy_diag(nx,:)=-2 
     527imx_diagl(nx,:)=-2 
     528imy_diagl(nx,:)=-2 
    591529 
    592530! Coins 
    593 imx_diag(2,1)=-41       ! SW 
    594 imy_diag(1,2)=-41 
    595  
    596 imx_diag(nx,1)=-12      ! SE 
    597 imy_diag(nx,2)=-12 
    598  
    599 imx_diag(nx,ny)=-23     ! NE 
    600 imy_diag(nx,ny)=-23 
    601  
    602 imx_diag(2,ny)=-34      ! NW 
    603 imy_diag(1,ny)=-34 
     531imx_diagl(2,1)=-41       ! SW 
     532imy_diagl(1,2)=-41 
     533 
     534imx_diagl(nx,1)=-12      ! SE 
     535imy_diagl(nx,2)=-12 
     536 
     537imx_diagl(nx,ny)=-23     ! NE 
     538imy_diagl(nx,ny)=-23 
     539 
     540imx_diagl(2,ny)=-34      ! NW 
     541imy_diagl(1,ny)=-34 
    604542 
    605543! hors domaine 
    606 imx_diag(1,:)=0     ! hors domaine a cause des mailles alternees 
    607 imy_diag(:,1)=0     ! hors domaine a cause des mailles alternees 
     544imx_diagl(1,:)=0     ! hors domaine a cause des mailles alternees 
     545imy_diagl(:,1)=0     ! hors domaine a cause des mailles alternees 
    608546!$OMP END WORKSHARE 
    609547!$OMP END PARALLEL 
     
    612550 
    613551 
    614 subroutine imx_imy_nx_ny_reduce(choix) 
    615  
    616 use module3d_phy, only: flot,imx_diag,imy_diag,gr_line  
    617           
     552subroutine imx_imy_nx_ny_reduce(choix,flot,imx_diag,imy_diag,gr_line) 
     553 
    618554implicit none 
    619555 
     
    621557!       We simply compute the velocities around (nneigh) the grounding line 
    622558 
    623   integer, intent(in) :: choix 
     559  integer,                 intent(in)    :: choix 
     560  logical, dimension(:,:), intent(in)    :: flot 
     561  integer, dimension(:,:), intent(in)    :: imx_diag,imy_diag,gr_line 
     562 
    624563 
    625564  integer i,j,nvx,nvy 
     
    717656end subroutine mismip_boundary_cond 
    718657 
    719 !end module diagno_L2_mod 
    720658end module diagno_mod 
Note: See TracChangeset for help on using the changeset viewer.