subroutine Kick_Influx    !  is called in subroutine CirculationCodeSelect
    
        Use GeoElements_FluidModule
        USE CMudPropertiesVariables
        USE MudSystemVARIABLES
use SimulationVariables !@@@
        use SimulationVariables
        use SimulationVariables !@
        !use CTanks
        ! !@use ConfigurationVariables, TripTankVolume2 => data%Equipments%DrillingWatch%TripTankVolume, TripTankDensity2 => TripTankDensity
        USE sROP_Other_Variables
        USE sROP_Variables
        use KickVARIABLESModule

   
   implicit none

   
!===========================================================WELL============================================================
!===========================================================WELL============================================================ 

            !write(*,*) 'Kick Influx'
  

!=================== Bottom Hole Kick Influx ENTRANCE(due to Kick) ===================
   
            data%State%MudSystem%Kick_Density= 2
            data%State%MudSystem%NewInflux_Density= data%State%MudSystem%Kick_Density
              
            
        if ( data%State%MudSystem%NewInfluxElementCreated==0 ) then ! new kick is pumped- (it is set to zero in sheykh subroutine after a new kick influx)
        call data%State%MudSystem%Op_Density%AddToFirst (data%State%MudSystem%NewInflux_Density)
        call data%State%MudSystem%Op_MudDischarged_Volume%AddToFirst (0.0d0)
        call data%State%MudSystem%Op_Mud_Forehead_X%AddToFirst (data%State%MudSystem%Xstart_OpSection(1))
        call data%State%MudSystem%Op_Mud_Forehead_section%AddToFirst (1)
        call data%State%MudSystem%Op_Mud_Backhead_X%AddToFirst (data%State%MudSystem%Xstart_OpSection(1))
        call data%State%MudSystem%Op_Mud_Backhead_section%AddToFirst (1)
        call data%State%MudSystem%Op_RemainedVolume_in_LastSection%AddToFirst (0.0d0)
        call data%State%MudSystem%Op_EmptyVolume_inBackheadLocation%AddToFirst (0.0d0)
        call data%State%MudSystem%Op_MudOrKick%AddToFirst (data%State%MudSystem%NewInfluxNumber)       ! KickNumber= NewInfluxNumber
        
         
            data%State%MudSystem%NewInfluxElementCreated= 1
        endif   
        

        data%State%MudSystem%Op_MudDischarged_Volume%Array(1)= data%State%MudSystem%Op_MudDischarged_Volume%Array(1)+ ((KickVARIABLES%GasKickPumpFlowRate/60.0d0)*data%State%MudSystem%DeltaT_Mudline)    !(gal)    due to KickFlux 
        !write(*,*) 'kick volume ok=' , Op_MudDischarged_Volume%Array(1)
              


    end subroutine Kick_Influx
    
    
    
    
    
    
    
    
    
    
    
subroutine Instructor_CirculationMud_Edit    !  is called in subroutine CirculationCodeSelect 

    use KickVARIABLESModule
    USE MudSystemVARIABLES
use SimulationVariables !@@@
    USE TD_DrillStemComponents
    Use CUnityInputs
    Use CUnityOutputs
    use OperationScenariosModule
    use UTUBEVARSModule
    use sROP_Variables
    use sROP_Other_Variables
    use CDownHoleVariables
    

    implicit none
    



            
            if ( data%Equipments%DownHole%AnnDrillMud == .true. .and. (data%State%ROP_Bit%RateOfPenetration>0. .and. data%State%MudSystem%DeltaVolumeOp>0.0) ) then
                
                do imud= 1, data%State%MudSystem%Ann_Density%Length()
                    
                    if ( data%State%MudSystem%Ann_MudOrKick%Array(imud) == 0 ) then
                        data%State%MudSystem%Ann_Density%Array(imud)= (data%State%MudSystem%St_Density%Last() * data%State%MudSystem%AnnulusFlowRate + 141.4296E-4*data%State%ROP_Bit%RateOfPenetration*data%State%ROP_Spec%DiameterOfBit**2)/(data%State%MudSystem%AnnulusFlowRate+6.7995E-4*data%State%ROP_Bit%RateOfPenetration*data%State%ROP_Spec%DiameterOfBit**2)
                        data%State%MudSystem%Ann_CuttingMud%Array(imud)= 1
                    endif
                    
                enddo
                
            endif
            
    
            if ( data%Equipments%DownHole%AnnCirculateMud == .true. ) then
                
                do imud= 1, data%State%MudSystem%Ann_Density%Length()
                    
                    if ( data%State%MudSystem%Ann_MudOrKick%Array(imud) == 0 ) then
                        data%State%MudSystem%Ann_Density%Array(imud)= data%State%MudSystem%ActiveTankDensity
                        data%State%MudSystem%Ann_CuttingMud%Array(imud)= 0
                    endif
                    
                enddo
                
                do imud= 1, data%State%MudSystem%St_Density%Length()
                    
                        data%State%MudSystem%St_Density%Array(imud)= data%State%MudSystem%ActiveTankDensity
                    
                enddo                
                
            endif            
            



    end subroutine Instructor_CirculationMud_Edit
    
    
    
subroutine ShoeLostSub    !  is called in subroutine CirculationCodeSelect 

    use KickVARIABLESModule
    USE MudSystemVARIABLES
use SimulationVariables !@@@
    USE TD_DrillStemComponents
    Use CUnityInputs
    Use CUnityOutputs
    use OperationScenariosModule
    use UTUBEVARSModule
    use sROP_Variables
    use sROP_Other_Variables
    use CDownHoleVariables
    use CShoeVariables
    use PressureDisplayVARIABLESModule
    use CWarnings
    

    implicit none   
    
            data%State%MudSystem%ShoeLost= .false.
            data%State%MudSystem%Kickexpansion_DueToMudLost= .false.
            
            data%State%MudSystem%ShoeMudPressure= data%State%PressureDisplay%PressureGauges(5)
            
            
            data%State%MudSystem%UGBOSuccessionCounter = data%State%MudSystem%UGBOSuccessionCounter + 1
            !write(*,*) 'check point 1'
            
            if (data%Configuration%Shoe%InactiveFracture == .FALSE. .AND. ((data%State%MudSystem%ShoeMudPressure >= data%State%MudSystem%FormationLostPressure) .or. data%State%MudSystem%ShoeFractured )) then
            !write(*,*) 'check point 2 ,UGBOSuccessionCounter' , UGBOSuccessionCounter
              
                ! if ShoeFractured changed to true , then time counter is not needed more
                    if ( data%State%MudSystem%UGBOSuccessionCounter /= data%State%MudSystem%UGBOSuccessionCounterOld+1 .and. data%State%MudSystem%ShoeFractured==.false. ) then
                        data%State%MudSystem%UGBOSuccessionCounter = 0   ! also in starup
                        data%State%MudSystem%UGBOSuccessionCounterOld = 0   ! also in starup
                        return   
                    else
                        data%State%MudSystem%UGBOSuccessionCounterOld= data%State%MudSystem%UGBOSuccessionCounter        
                    endif

                    if ( data%State%MudSystem%UGBOSuccessionCounter < 10 .and. data%State%MudSystem%ShoeFractured==.false.) then
                        return
                    endif 
                
            !write(*,*) 'check point 3 ,UGBOSuccessionCounter' , UGBOSuccessionCounter
                
     
                
                data%State%MudSystem%ShoeFractured= .true.
                
                data%State%MudSystem%ShoeMudViscosity= MAX(data%State%MudSystem%ShoeMudViscosity, 12.d0)
                !write(*,*) 'ShoeMudDensity , ShoeMudViscosity' , ShoeMudDensity , ShoeMudViscosity
                data%State%MudSystem%ShoeLostCoef = 10.**(-8) * 1.15741d0 * 7.08d0 * 1000000.d0 * 1.d0 * data%State%MudSystem%ShoeMudDensity / &
                            (data%State%MudSystem%ShoeMudViscosity * LOG(10000.d0))
                !write(*,*) 'lost parameters 1' , ShoeMudPressure , FormationLostPressure
                data%State%MudSystem%Qlost = MAX( (data%State%MudSystem%ShoeLostCoef * (data%State%MudSystem%ShoeMudPressure - (data%State%MudSystem%FormationLostPressure/2.0))) , 0.d0 )
                if (data%State%MudSystem%Qlost > 0.0) then
                    data%State%MudSystem%ShoeLost= .true.
                else
                    data%State%MudSystem%ShoeLost= .false.
                endif
                
                !write(*,*) 'Qlost=' , Qlost, ShoeMudPressure, FormationLostPressure
                call Activate_UndergroundBlowout()
                
                
                do imud= 1, data%State%MudSystem%Ann_Mud_Forehead_X%Length()

                        IF ( data%State%MudSystem%ShoeLost .and. data%Configuration%Shoe%ShoeDepth < data%State%MudSystem%Ann_Mud_Backhead_X%Array(imud) .and. data%Configuration%Shoe%ShoeDepth >= data%State%MudSystem%Ann_Mud_Forehead_X%Array(imud) &
                            .and. data%State%MudSystem%Ann_MudOrKick%Array(imud) == 0 .and. data%State%MudSystem%WellHeadIsOpen == .FALSE. ) then
                
                            data%State%MudSystem%Kickexpansion_DueToMudLost= .true.
                            write(*,*) 'Kickexpansion_DueToMudLost'
                            
                            EXIT
 
                        ENDIF
                
     
                enddo
    

                
            endif
            
            if (data%Warnings%UndergroundBlowout == .false.) data%State%MudSystem%ShoeLost= .false.    
    
    
    
    end subroutine ShoeLostSub