|
123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596 |
- subroutine TD_MudPropertiesReadData (i)
-
- Use TD_DrillStemComponents
- Use TD_WellElements
- Use TD_WellGeometry
- Use TD_GeneralData
- Use FricPressDropVars
- Use MudSystemVARIABLES
-
- implicit none
-
-
-
- Integer :: i , j , TDmd
- real(8) :: TDden, TDpre, TDtem
-
-
-
- !====================================================
- ! Set Mud Properties Data
- !====================================================
- IF ( ALLOCATED(FlowEl) ) THEN
- if ( i==2 ) then
- TDmd = int(TD_DrillStems(i)%DownDepthIni-1.d0)
- else
- TDmd = int(TD_DrillStems(i)%DownDepthIni)
- end if
- Call StringPropertyCalculator (TDmd , TDden, TDpre, TDtem)
- TD_DrillStems(i)%MudDensityIn = TDden*7.48051948d0 ! [ppg]*7.48051948=[lb/ft3]
- Call AnnulusPropertyCalculator (TDmd , TDden, TDpre, TDtem)
- TD_DrillStems(i)%MudDensityOut = TDden*7.48051948d0 ! [ppg]*7.48051948=[lb/ft3]
- TD_DrillStems(i)%MudWeight = TDden ! [ppg] ???????????????
- ELSE
- TD_DrillStems(i)%MudDensityIn = TD_DrillStems(i)%MudDensityIn
- TD_DrillStems(i)%MudDensityOut = TD_DrillStems(i)%MudDensityOut
- TD_DrillStems(i)%MudWeight = TD_DrillStems(i)%MudWeight
- END IF
-
-
- !TD_DrillStems(i)%Drag =
-
-
-
-
-
- !IF (ALLOCATED(TD_FluidMudDensity) .and. ALLOCATED(TD_FluidMudStartX) .and. TD_NoStringMudElements/=0) THEN
- ! Do j = TD_NoHorizontalMudElements+1,TD_NoHorizontalMudElements+TD_NoStringMudElements
- ! if ( TD_DrillStems(i)%DownDepthIni<=TD_FluidMudStartX(j) ) then
- ! exit
- ! end if
- ! TD_DrillStems(i)%MudDensityIn = TD_FluidMudDensity(j)*7.48051948d0 !10.*7.48051948 ! [ppg]*7.48051948=[lb/ft3]
- ! !print*, 'TD_DrillStems(i)%MudDensityIn=' ,TD_DrillStems(i)%MudDensityIn , i
- ! !print*, 'FlowEl(j)%density=' ,FlowEl(j)%density , i
- ! End Do
- !ELSE
- ! TD_DrillStems(i)%MudDensityIn = TD_DrillStems(i)%MudDensityIn ! [ppg]*7.48051948=[lb/ft3]
- !! !print*, '=================' , i
- !END IF
- !
- !
- !
- !
- !
- !
- !
- !IF (ALLOCATED(TD_FluidMudDensity) .and. ALLOCATED(TD_FluidMudEndX) .and. TD_NoCasingMudElements/=0) THEN
- ! Do j = (TD_NoHorizontalMudElements+TD_NoStringMudElements+TD_NoCasingMudElements),(TD_NoHorizontalMudElements+TD_NoStringMudElements+1),-1
- ! if ( TD_DrillStems(i)%DownDepthIni<=TD_FluidMudEndX(j) ) then
- ! exit
- ! end if
- ! TD_DrillStems(i)%MudDensityOut = TD_FluidMudDensity(j)*7.48051948d0 !10.*7.48051948 ! [ppg]*7.48051948=[lb/ft3]
- ! TD_DrillStems(i)%MudWeight = TD_FluidMudDensity(j) !10.0 ! [ppg] ???????????????
- ! End Do
- !ELSE
- ! TD_DrillStems(i)%MudDensityOut = TD_DrillStems(i)%MudDensityOut ! [ppg]*7.48051948=[lb/ft3]
- ! TD_DrillStems(i)%MudWeight = TD_DrillStems(i)%MudWeight ! [ppg] ???????????????
- !END IF
-
-
-
-
-
-
-
-
- TD_DrillStems(i)%MudPlasticVis = 5.d0+(5.d0*(TD_DrillStems(i)%MudWeight-8.3d0)) ! [cP]
- !TD_DrillStems(i)%MudPlasticVis= TD_DrillStems(i)%MudPlasticVis * 6.71968d-4 ! [cP]*6.71968d-4=[lb/(ft.s)]
- TD_DrillStems(i)%MudViscosity = 0.2d0 !TD_DrillStems(i)%MudPlasticVis
- TD_DrillStems(i)%MudYieldPoint = 10.d0+(TD_DrillStems(i)%MudWeight-8.3d0)
-
-
-
-
-
-
- end subroutine
|