subroutine DisconnectingPipe    !  is called in subroutine CirculationCodeSelect
    
        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
        USE TD_DrillStemComponents
        use OperationScenariosModule
        Use CUnityOutputs
        USE CManifolds
   
   implicit none
   
   Real(8) ExcessMudVolume, ExcessMudVolume_Remained
            write(*,*) 'DisconnectingPipe'
  
        !TD_RemoveVolume= TD_RemoveVolume* 7.48051948        ! ft^3  to gal         

        ExcessMudVolume= sum(data%State%MudSystem%St_MudDischarged_Volume%Array(:)) - sum(data%State%MudSystem%PipeSection_VolumeCapacity(2:data%State%F_Counts%StringIntervalCounts))
        
        
        !       ======if(ExcessMudVolume <= 0.)  No Modification Needed Because Removed Pipe was Empty=====
        
        if (Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and. Manifold%Valve(56)%Status == .False.) ExcessMudVolume= 0.d0  !Valve(56)%Status == .False. :: safety valve installed
        
        if (ExcessMudVolume > 0.) then
            
            if ( Manifold%Valve(53)%Status == .true. ) then
                data%State%MudSystem%MudBucketVolume= ExcessMudVolume
            else
                data%State%MudSystem%MudBucketVolume= 0.0
            endif
            
                
                
            
            
!========================Flow Disconnect Unity Input Signals=================         
            
            !if ( Get_JointConnectionPossible() == .false. ) then
                if (Get_KellyConnection() == KELLY_CONNECTION_NOTHING) then
                    Call Set_FlowKellyDisconnect(.true.)
                else
                    Call Set_FlowPipeDisconnect(.true.)
                endif
            !endif
            
 
            
!====================Flow Disconnect Unity Input Signals-End=================         
            
            
            
            
!========================Disconnecting Pipe from the String=================         
          
         ExcessMudVolume_Remained= ExcessMudVolume        ! ft^3  to gal         
          
            
            imud=1
           
            Do
                
                if(data%State%MudSystem%St_MudDischarged_Volume%Array(imud) < ExcessMudVolume_Remained) then
                    ExcessMudVolume_Remained= ExcessMudVolume_Remained- data%State%MudSystem%St_MudDischarged_Volume%Array(imud)
                    call data%State%MudSystem%St_MudDischarged_Volume%Remove (imud)
                    call data%State%MudSystem%St_Mud_Backhead_X%Remove (imud)
                    call data%State%MudSystem%St_Mud_Backhead_section%Remove (imud)
                    call data%State%MudSystem%St_Mud_Forehead_X%Remove (imud)
                    call data%State%MudSystem%St_Mud_Forehead_section%Remove (imud)
                    call data%State%MudSystem%St_Density%Remove (imud)
                    call data%State%MudSystem%St_RemainedVolume_in_LastSection%Remove (imud)
                    call data%State%MudSystem%St_EmptyVolume_inBackheadLocation%Remove (imud)
                    call data%State%MudSystem%St_MudOrKick%Remove (imud)  
                    
                elseif(data%State%MudSystem%St_MudDischarged_Volume%Array(imud) > ExcessMudVolume_Remained) then
                    data%State%MudSystem%St_MudDischarged_Volume%Array(imud)= data%State%MudSystem%St_MudDischarged_Volume%Array(imud)- ExcessMudVolume_Remained
                    exit
                    
                else    !(St_MudDischarged_Volume%Array(imud) == ExcessMudVolume_Remained) 
                    call data%State%MudSystem%St_MudDischarged_Volume%Remove (imud)
                    call data%State%MudSystem%St_Mud_Backhead_X%Remove (imud)
                    call data%State%MudSystem%St_Mud_Backhead_section%Remove (imud)
                    call data%State%MudSystem%St_Mud_Forehead_X%Remove (imud)
                    call data%State%MudSystem%St_Mud_Forehead_section%Remove (imud)
                    call data%State%MudSystem%St_Density%Remove (imud)
                    call data%State%MudSystem%St_RemainedVolume_in_LastSection%Remove (imud)
                    call data%State%MudSystem%St_EmptyVolume_inBackheadLocation%Remove (imud)
                    call data%State%MudSystem%St_MudOrKick%Remove (imud) 
                    exit
                    
                endif
                
            enddo
            
            
            
        
!=================Disconnecting Pipe from the String - End===================    
        endif
    
        
    end subroutine DisconnectingPipe