subroutine FillingWell_By_BellNipple    !  is called in subroutine CirculationCodeSelect        
    
   ! this subroutine is for lines:   1) BellNippleToWell-NonFullWell : data%State%MUD(8)%Q   
   !                                 2) PumpsToWell_KillLine : data%State%MUD(10)%Q
    
        Use GeoElements_FluidModule
        USE CMudPropertiesVariables
        USE MudSystemVARIABLES
use SimulationVariables !@@@
        use SimulationVariables
        use SimulationVariables !@
        !use CTanks
    !@use ConfigurationVariables, TripTankVolume2 => data%EquipmentControl%DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
        USE sROP_Other_Variables
        USE sROP_Variables
        use KickVARIABLESModule
   
   implicit none
   
 real(8)  deltaV,Xposition,FillingDensity
 
 integer kloc,SectionPosition
   

   
   
                      ! Well Is Not Full
   
   
   
    if (data%State%MudSystem%Ann_MudOrKick%Last() == 104) then      ! Last Element is air      we must observe: Ann_Mud_Forehead_X%Last()=0.0
        
        write(*,*) 'FillingWell_By_BellNipple-Last Element is air'
        
        !write(*,*)  '*Ann_Mud_Forehead_X%Last()=' , Ann_Mud_Forehead_X%Last()
        !write(*,*)  '*Ann_MudOrKick%Last()=' , Ann_MudOrKick%Last()
        
            
    
            FillingDensity= data%State%MudSystem%BellNippleDensity
            
!****************************            
            if ( data%State%MudSystem%Ann_MudDischarged_Volume%Last() > (((data%State%MUD(8)%Q+data%State%MUD(10)%Q)/60.)*data%State%MudSystem%DeltaT_Mudline)) then    ! air baghi mimune
                
                kloc= data%State%MudSystem%Ann_MudDischarged_Volume%Length()-1
                
                
                
                deltaV= ((data%State%MUD(8)%Q+data%State%MUD(10)%Q)/60.)*data%State%MudSystem%DeltaT_Mudline
                
                data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%Ann_MudDischarged_Volume%Length())= data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%Ann_MudDischarged_Volume%Length()) - deltaV
                
   
!========================ANNULUS ENTRANCE==================== 
        
         if (ABS(data%State%MudSystem%Ann_Density%Array(kloc) - FillingDensity) >= data%State%MudSystem%DensityMixTol) then     ! new mud is pumped
            call data%State%MudSystem%Ann_Density%AddTo (kloc, FillingDensity)   
            call data%State%MudSystem%Ann_MudDischarged_Volume%AddTo (kloc, 0.0d0)
            call data%State%MudSystem%Ann_Mud_Forehead_X%AddTo (kloc, 0.0d0)
            call data%State%MudSystem%Ann_Mud_Forehead_section%AddTo (kloc, 1)
            call data%State%MudSystem%Ann_Mud_Backhead_X%AddTo (kloc, 0.0d0)
            call data%State%MudSystem%Ann_Mud_Backhead_section%AddTo (kloc, data%State%MudSystem%NoPipeSections)
            call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%AddTo (kloc, 0.0d0)
            call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%AddTo (kloc, 0.0d0)
            call data%State%MudSystem%Ann_MudOrKick%AddTo (kloc, 0)
            call data%State%MudSystem%Ann_CuttingMud%AddTo (kloc,0) 
             
             !AnnulusSuctionDensity_Old= Hz_Density_Utube
         endif    
            
!========================ANNULUS==================== 

     data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)+ deltaV    !(gal)
     
     
     
            else       ! ( Ann_MudDischarged_Volume%Last() <= (((data%State%MUD(8)%Q+data%State%MUD(10)%Q)/60.)*DeltaT_Mudline)) then    ! air baghi namune

                
                
                
                kloc= data%State%MudSystem%Ann_MudDischarged_Volume%Length()-1
                
                deltaV= data%State%MudSystem%Ann_MudDischarged_Volume%Last()
                
                
                
                if (ABS(data%State%MudSystem%Ann_Density%Array(kloc)-FillingDensity)< data%State%MudSystem%DensityMixTol .and. data%State%MudSystem%Ann_CuttingMud%Array(kloc)==0) then    ! .OR. (Ann_MudDischarged_Volume%Array(kloc)< 42.) ) then      ! 1-Pockets are Merged
                     data%State%MudSystem%Ann_Density%Array(kloc)= (data%State%MudSystem%Ann_Density%Array(kloc)*data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)+FillingDensity*deltaV)/(data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV)
                     data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV
                     data%State%MudSystem%Ann_Mud_Forehead_X%Array(kloc)= data%State%MudSystem%Xend_PipeSection(data%State%MudSystem%NoPipeSections)
                     data%State%MudSystem%Ann_Mud_Forehead_section%Array(kloc)= data%State%MudSystem%NoPipeSections
                     !Ann_Mud_Backhead_X%Array(kloc)= no change
                     !Ann_Mud_Backhead_section%Array(kloc)= no change
                     data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(kloc)= (0.0)
                     data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(kloc)= (0.0) 
                 
                    call data%State%MudSystem%Ann_MudDischarged_Volume%Remove (kloc+1)
                    call data%State%MudSystem%Ann_Mud_Backhead_X%Remove (kloc+1)
                    call data%State%MudSystem%Ann_Mud_Backhead_section%Remove (kloc+1)
                    call data%State%MudSystem%Ann_Mud_Forehead_X%Remove (kloc+1)
                    call data%State%MudSystem%Ann_Mud_Forehead_section%Remove (kloc+1)
                    call data%State%MudSystem%Ann_Density%Remove (kloc+1)
                    call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Remove (kloc+1)
                    call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Remove (kloc+1)
                    call data%State%MudSystem%Ann_MudOrKick%Remove (kloc+1)
                    call data%State%MudSystem%Ann_CuttingMud%Remove (kloc+1)
                 
                 
                else        ! 2-Merging conditions are not meeted, so new pocket== air is replaced with filling mud
                    data%State%MudSystem%Ann_Density%Array(kloc+1) =FillingDensity
                    data%State%MudSystem%Ann_MudOrKick%Array(kloc+1)= 0
                
                endif                

                
            endif
            
            ! end condition (Ann_MudOrKick%Last() == 104)  ! Last Element is air
            
!********************************************************************************************************************************************************** 
            
            
            
            
    else       ! (Ann_MudOrKick%Last() == 0) then      ! Last Element is  NOT air-      so we must observe: Ann_Mud_Forehead_X%Last()/=0.0
        
        !write(*,*) 'FillingWell_By_BellNipple-Last Element is NOT air'
        !
        !write(*,*)  '*Ann_Mud_Forehead_X%Last()=' , Ann_Mud_Forehead_X%Last()
        !write(*,*)  '*Ann_MudOrKick%Last()=' , Ann_MudOrKick%Last()
        
        
                deltaV= ((data%State%MUD(8)%Q+data%State%MUD(10)%Q)/60.)*data%State%MudSystem%DeltaT_Mudline
                
                kloc= data%State%MudSystem%Ann_MudDischarged_Volume%Length()
                
                

                
   
!========================ANNULUS ENTRANCE==================== 
        
             if (ABS(data%State%MudSystem%Ann_Density%Last() - FillingDensity) >= data%State%MudSystem%DensityMixTol .or. data%State%MudSystem%Ann_CuttingMud%Last()==1) then    ! .OR. (Ann_MudDischarged_Volume%Array(kloc)>42.) ) then     ! new mud is pumped
                 Xposition= data%State%MudSystem%Ann_Mud_Forehead_X%Last()
                 SectionPosition= data%State%MudSystem%Ann_Mud_Forehead_section%Last()
                call data%State%MudSystem%Ann_Density%Add (FillingDensity)   
                call data%State%MudSystem%Ann_MudDischarged_Volume%Add (0.0d0)
                call data%State%MudSystem%Ann_Mud_Forehead_X%Add (Xposition)
                call data%State%MudSystem%Ann_Mud_Forehead_section%Add (SectionPosition)
                call data%State%MudSystem%Ann_Mud_Backhead_X%Add (Xposition)
                call data%State%MudSystem%Ann_Mud_Backhead_section%Add (SectionPosition)
                call data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Add (0.0d0)
                call data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Add (0.0d0)
                call data%State%MudSystem%Ann_MudOrKick%Add (0)
                call data%State%MudSystem%Ann_CuttingMud%Add (0)
             
                 !AnnulusSuctionDensity_Old= Hz_Density_Utube
             !endif    
            
!========================ANNULUS==================== 

            data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%Ann_MudDischarged_Volume%Length())= data%State%MudSystem%Ann_MudDischarged_Volume%Array(data%State%MudSystem%Ann_MudDischarged_Volume%Length())+ deltaV    !(gal)  
     
     
             else     !  Merged with last Mud
                    data%State%MudSystem%Ann_Density%Array(kloc)= (data%State%MudSystem%Ann_Density%Array(kloc)*data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)+FillingDensity*deltaV)/(data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV)
                    data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)= data%State%MudSystem%Ann_MudDischarged_Volume%Array(kloc)+deltaV
                    !Ann_Mud_Forehead_X%Array(kloc)= Xend_PipeSection(NoPipeSections)
                    !Ann_Mud_Forehead_section%Array(kloc)= NoPipeSections
                    !Ann_Mud_Backhead_X%Array(kloc)= no change
                    !Ann_Mud_Backhead_section%Array(kloc)= no change
                    data%State%MudSystem%Ann_RemainedVolume_in_LastSection%Array(kloc)= (0.0)
                    data%State%MudSystem%Ann_EmptyVolume_inBackheadLocation%Array(kloc)= (0.0) 
             endif
         
         
         

        
        
    endif
    
        
            
                  
         

         
         
         
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
   
    
        
    end subroutine FillingWell_By_BellNipple