@@ -20,6 +20,7 @@ module CFormation | |||
call json%info(p, n_children=n_children) | |||
data%Configuration%Formation%Count = n_children | |||
if (.not. allocated(data%Configuration%Formation%Formations) .or. size(data%Configuration%Formation%Formations)/=n_children) then | |||
ALLOCATE(data%Configuration%Formation%Formations(n_children)) | |||
endif | |||
@@ -54,7 +54,6 @@ module CPathGeneration | |||
call json%get(parent,'Path',p) | |||
call json%get(p,'Items',pitems) | |||
call json%info(pitems, n_children=n_children) | |||
if (.not. allocated(data%Configuration%Path%Items)) then | |||
ALLOCATE(data%Configuration%Path%Items(n_children)) | |||
endif | |||
@@ -51,8 +51,8 @@ module DownHoleModule | |||
integer :: i, offset | |||
type(CFluid), intent(inout), target :: array(count) | |||
type(CFluid), pointer :: item | |||
data%Equipments%DownHole%AnnalusFluidsCount = count | |||
if(print_log) print*, 'AnnalusFluidsCount = ', count | |||
! data%Equipments%DownHole%AnnalusFluidsCount = count | |||
! if(print_log) print*, 'AnnalusFluidsCount = ', count | |||
if(size(data%Equipments%DownHole%AnnalusFluids) > 0) then | |||
deallocate(data%Equipments%DownHole%AnnalusFluids) | |||
end if | |||
@@ -103,7 +103,7 @@ module DownHoleModule | |||
type(CFluid), intent(inout), target :: array(count) | |||
type(CFluid), pointer :: item | |||
data%Equipments%DownHole%StringFluidsCount = count | |||
if(print_log) print*, 'StringFluidsCount = ', count | |||
! if(print_log) print*, 'StringFluidsCount = ', count | |||
if(size(data%Equipments%DownHole%StringFluids) > 0) then | |||
deallocate(data%Equipments%DownHole%StringFluids) | |||
end if | |||
@@ -21,7 +21,7 @@ module CChokeControlPanel | |||
if ( .not. found ) call logg(4,"Not found: ChokeControlPanel%ChokeControlLever") | |||
call jsonfile%get('Equipments.ChokeControl.ChokePanelRigAirSwitch',data%Equipments%ChokeControlPanel%ChokePanelRigAirSwitch,found) | |||
if ( .not. found ) call logg(4,"Not found: ChokeControlPanel%ChokePanelRigAirSwitch") | |||
print *,data%Equipments%ChokeControlPanel%ChokeSelectorSwitch | |||
! print *,data%Equipments%ChokeControlPanel%ChokeSelectorSwitch | |||
end subroutine | |||
subroutine ChokeControlPanelToJson(parent) | |||
@@ -33,9 +33,9 @@ module CChokeControlPanel | |||
! 1. create new node | |||
call json%create_object(p,'ChokeControl') | |||
call json%add(p,"ChokePanelPumpSelectorSwitch",data%Equipments%ChokeControlPanel%ChokePanelPumpSelectorSwitch) | |||
! call json%add(p,"ChokePanelStrokeResetSwitch",data%Equipments%ChokeControlPanel%ChokePanelStrokeResetSwitch) | |||
call json%add(p,"ChokePanelStrokeResetSwitch",data%Equipments%ChokeControlPanel%ChokePanelStrokeResetSwitch) | |||
call json%add(p,"ChokeSelectorSwitch",data%Equipments%ChokeControlPanel%ChokeSelectorSwitch) | |||
! call json%add(p,"ChokeRateControlKnob",data%Equipments%ChokeControlPanel%ChokeRateControlKnob) | |||
call json%add(p,"ChokeRateControlKnob",data%Equipments%ChokeControlPanel%ChokeRateControlKnob) | |||
call json%add(p,"ChokeControlLever",data%Equipments%ChokeControlPanel%ChokeControlLever) | |||
call json%add(p,"ChokePanelRigAirSwitch",data%Equipments%ChokeControlPanel%ChokePanelRigAirSwitch) | |||
! call json%add(p,"EnableAutoChoke",data%Equipments%ChokeControlPanel%EnableAutoChoke) | |||
@@ -96,9 +96,9 @@ module CChokeManifold | |||
call ChangeValve(33, .true.) | |||
else | |||
if(v == 100) then | |||
if(Manifold%Valve(33)%Status) call ChangeValve(33, .false.) | |||
if(data%state%manifold%Valve(33)%Status) call ChangeValve(33, .false.) | |||
else | |||
if(.not.Manifold%Valve(33)%Status) call ChangeValve(33, .true.) | |||
if(.not.data%state%manifold%Valve(33)%Status) call ChangeValve(33, .true.) | |||
endif | |||
endif | |||
!WRITE (*,*) ' valve 33 ', Valve(33)%Status, ' arg ', v | |||
@@ -112,9 +112,9 @@ subroutine SetHydraulicChock2(v) | |||
call ChangeValve(34, .true.) | |||
else | |||
if(v==100) then | |||
if(Manifold%Valve(34)%Status) call ChangeValve(34, .false.) | |||
if(data%state%manifold%Valve(34)%Status) call ChangeValve(34, .false.) | |||
else | |||
if(.not.Manifold%Valve(34)%Status) call ChangeValve(34, .true.) | |||
if(.not.data%state%manifold%Valve(34)%Status) call ChangeValve(34, .true.) | |||
endif | |||
endif | |||
!WRITE (*,*) ' valve 34 ', Valve(34)%Status, ' arg ', v | |||
@@ -108,7 +108,6 @@ module CDataDisplayConsole | |||
end subroutine | |||
subroutine DataDisplayConsoleToJson(parent) | |||
type(json_value),pointer :: parent | |||
type(json_core) :: json | |||
type(json_value),pointer :: p | |||
@@ -43,6 +43,7 @@ module CDrillingConsole | |||
if ( .not. found ) call logg(4,"Not found: DWSwitch") | |||
call jsonfile%get('Equipments.Drilling.DWThrottle',data%Equipments%DrillingConsole%DWThrottle,found) | |||
if ( .not. found ) call logg(4,"Not found: DWThrottle") | |||
if (print_log .and. abs(data%Equipments%DrillingConsole%DWThrottle)>0) print *,"data%Equipments%DrillingConsole%DWThrottle = ",data%Equipments%DrillingConsole%DWThrottle | |||
call jsonfile%get('Equipments.Drilling.RTSwitch',data%Equipments%DrillingConsole%RTSwitch,found) | |||
if ( .not. found ) call logg(4,"Not found: RTSwitch") | |||
call jsonfile%get('Equipments.Drilling.RTThrottle',i,found) | |||
@@ -5,34 +5,24 @@ module CHook | |||
public | |||
contains | |||
subroutine HookFromJson(parent) | |||
type(json_value),pointer :: parent | |||
type(json_core) :: json | |||
type(json_value),pointer :: p,pval | |||
! subroutine HookFromJson(jsonfile) | |||
! type(json_file)::jsonfile | |||
! logical::found | |||
! 1. get related root | |||
! call json%get(parent,'Hook',p) | |||
! ! 2. get member of data type from node | |||
! call json%get(p,'HookHeight_S',pval) | |||
! call json%get(pval,data%Equipments%Hook%HookHeight_S) | |||
! call json%get(p,'HookHeight',pval) | |||
! call json%get(pval,data%Equipments%Hook%HookHeight) | |||
end subroutine | |||
subroutine HookToJson(parent) | |||
! call jsonfile%get('Equipments.HookHeight',data%State%Drawworks%Hook_Height_final,found) | |||
! if ( .not. found ) call logg(4,"Not found: Equipments.Hook.HookHeight") | |||
! end subroutine | |||
type(json_value),pointer :: parent | |||
type(json_core) :: json | |||
type(json_value),pointer :: p | |||
! subroutine HookToJson(parent) | |||
! type(json_value),pointer :: parent | |||
! type(json_core) :: json | |||
! type(json_value),pointer :: p | |||
! 1. create new node | |||
call json%create_object(p,'Hook') | |||
call json%add(p,"HookHeight_S",data%Equipments%Hook%HookHeight_S) | |||
call json%add(p,"HookHeight",data%Equipments%Hook%HookHeight) | |||
call json%add(parent,p) | |||
end subroutine | |||
! ! 1. create new node | |||
! call json%create_object(p,'Hook') | |||
! call json%add(p,"Velocity",data%State%Drawworks%HookLinearVelocity_final) | |||
! call json%add(parent,p) | |||
! end subroutine | |||
subroutine Set_HookHeight(v) | |||
use CDrillingConsoleVariables | |||
@@ -1,7 +1,7 @@ | |||
module CStandPipeManifoldVariables | |||
implicit none | |||
public | |||
!TODO: check and remove is unused | |||
Type::StandPipeManifoldType | |||
! Input vars | |||
logical :: StandPipeManifoldValve1 | |||
@@ -0,0 +1,37 @@ | |||
module ManifoldVariables | |||
use CStack | |||
use CArrangement | |||
! use SimulationVariables | |||
! use CStandPipeManifoldVariables | |||
implicit none | |||
public | |||
integer, parameter :: ValveCount = 128 | |||
integer, parameter :: MinSource = 71 | |||
integer, parameter :: MaxSource = 90 | |||
integer, parameter :: MinRelation = 91 | |||
integer, parameter :: MaxRelation = 128 | |||
Type::ManifoldType | |||
type(Arrangement) :: Valve(ValveCount) | |||
type(Path), allocatable :: OpenPaths(:) | |||
type(Stack) :: Fringe | |||
logical :: IsRepititveOutput | |||
logical :: IsSafetyValveInstalled | |||
logical :: IsSafetyValveInstalled_KellyMode | |||
logical :: IsSafetyValveInstalled_TripMode | |||
logical :: IsSafetyValveInstalled_TopDrive | |||
logical :: SafetyValve | |||
logical :: IsIBopInstalled | |||
logical :: IBop | |||
logical :: IsKellyCockInstalled | |||
logical :: KellyCock | |||
logical :: IsTopDriveIBopInstalled | |||
logical :: TopDriveIBop | |||
logical :: IsFloatValveInstalled | |||
logical :: FloatValve | |||
logical :: IsPathsDirty = .false. | |||
logical :: IsTraverse = .false. | |||
End type ManifoldType | |||
End module ManifoldVariables |
@@ -6,12 +6,8 @@ module CTongNotification | |||
subroutine Evaluate_TongNotification() | |||
implicit none | |||
if (data%Configuration%Hoisting%DriveType == TopDrive_DriveType) then | |||
if(print_log) print*, 'Evaluate_TongNotification=TopDrive' | |||
! if(print_log) print*, 'Evaluate_TongNotification=TopDrive' | |||
!TOPDRIVE-CODE=50 | |||
if (((Get_HookHeight() >= (TL() + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + NFC() - data%State%OperationScenario%RE) .and. Get_HookHeight() <= (TL() + NFC() + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + data%State%OperationScenario%TG)) .or.& | |||
@@ -55,19 +51,8 @@ module CTongNotification | |||
endif | |||
if (data%Configuration%Hoisting%DriveType == Kelly_DriveType) then | |||
#ifdef OST | |||
if(print_log) print*, 'Evaluate_TongNotification=Kelly' | |||
#endif | |||
! if(print_log) print*, 'Evaluate_TongNotification=Kelly' | |||
!OPERATION-CODE=44 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
!((Get_HookHeight() >= 65.0 .and. Get_HookHeight() <= 70.0) .or.& | |||
@@ -86,9 +71,6 @@ module CTongNotification | |||
return | |||
end if | |||
!OPERATION-CODE=45 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_HookHeight() >= 66 .and. Get_HookHeight() <= 69 .and.& | |||
@@ -101,8 +83,6 @@ module CTongNotification | |||
return | |||
end if | |||
!OPERATION-CODE=46 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
Get_JointConnectionPossible() .and.& | |||
@@ -115,9 +95,6 @@ module CTongNotification | |||
return | |||
end if | |||
!OPERATION-CODE=47 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
@@ -130,11 +107,7 @@ module CTongNotification | |||
call Set_TongNotification(.true.) | |||
return | |||
end if | |||
end if | |||
!OPERATION-CODE=48 | |||
if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
@@ -149,21 +122,7 @@ module CTongNotification | |||
call Set_TongNotification(.true.) | |||
return | |||
end if | |||
!OPERATION-CODE=50 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
((Get_HookHeight() >= (data%State%OperationScenario%HL + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + Get_NearFloorConnection() - data%State%OperationScenario%RE) .and. Get_HookHeight() <= (data%State%OperationScenario%HL + Get_NearFloorConnection() + data%State%OperationScenario%PL - data%State%OperationScenario%ECG + data%State%OperationScenario%TG)) .or.& | |||
@@ -197,11 +156,7 @@ module CTongNotification | |||
call Set_TongNotification(.true.) | |||
return | |||
end if | |||
!OPERATION-CODE=52 | |||
if (Get_OperationCondition() == OPERATION_TRIP .and.& | |||
GetRotaryRpm() == 0.0d0 .and.& | |||
@@ -215,9 +170,6 @@ module CTongNotification | |||
call Set_TongNotification(.true.) | |||
return | |||
end if | |||
!if (Get_OperationCondition() == OPERATION_DRILL .and.& | |||
! Get_KellyConnection() == KELLY_CONNECTION_STRING .and.& | |||
@@ -233,14 +185,6 @@ module CTongNotification | |||
call Set_TongNotification(.true.) | |||
end subroutine | |||
! subroutine Subscribe_TongNotification() | |||
@@ -251,8 +251,8 @@ contains | |||
subroutine Set_IrSafetyValveLed(v) | |||
use CDrillingConsoleVariables | |||
use SimulationVariables | |||
use SimulationVariables!, only: data%Equipments%DrillingConsole%CloseKellyCockLed => IRSafetyValveLed | |||
use SimulationVariables | |||
use UnitySignalsModule | |||
use CManifolds, only: & | |||
InstallSafetyValve_TopDrive, & | |||
InstallSafetyValve_KellyMode, & | |||
@@ -261,31 +261,24 @@ contains | |||
RemoveSafetyValve_KellyMode, & | |||
RemoveSafetyValve_TripMode | |||
use UnitySignalVariables | |||
use UnitySignalsModule, only: Set_SafetyValve_Install, Set_SafetyValve_Remove | |||
use CHoistingVariables | |||
use SimulationVariables!, only: data%Configuration%Hoisting%DriveType, TopDrive_DriveType, Kelly_DriveType | |||
implicit none | |||
logical , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
if(data%State%notifications%IrSafetyValveLed == v) return | |||
if(data%State%notifications%IrSafetyValveLed == v) return | |||
#endif | |||
data%State%notifications%IrSafetyValveLed = v | |||
if(data%State%notifications%IrSafetyValveLed) then | |||
data%Equipments%DrillingConsole%IRSafetyValveLed = 1 | |||
if(data%Configuration%Hoisting%DriveType == TopDrive_DriveType) call InstallSafetyValve_TopDrive() | |||
if(data%Configuration%Hoisting%DriveType == Kelly_DriveType .and. data%State%notifications%operation_IrSafetyValveLed == 0) call InstallSafetyValve_KellyMode() | |||
if(data%Configuration%Hoisting%DriveType == Kelly_DriveType .and. data%State%notifications%operation_IrSafetyValveLed == 1) call InstallSafetyValve_TripMode() | |||
call Set_SafetyValve_Install() | |||
else | |||
data%Equipments%DrillingConsole%IRSafetyValveLed = 0 | |||
if(data%Configuration%Hoisting%DriveType == TopDrive_DriveType) call RemoveSafetyValve_TopDrive() | |||
if(data%Configuration%Hoisting%DriveType == Kelly_DriveType .and. data%State%notifications%operation_IrSafetyValveLed == 0) call RemoveSafetyValve_KellyMode() | |||
if(data%Configuration%Hoisting%DriveType == Kelly_DriveType .and. data%State%notifications%operation_IrSafetyValveLed == 1) call RemoveSafetyValve_TripMode() | |||
call Set_SafetyValve_Remove() | |||
endif | |||
@@ -299,11 +292,11 @@ contains | |||
subroutine Set_IrIBopLed(v) | |||
use CDrillingConsoleVariables | |||
use SimulationVariables | |||
use SimulationVariables!, only: IRIBopLedHw => IRIBopLed | |||
use SimulationVariables | |||
use SimulationVariables!, only: IRIBopLedHw => IRIBopLed | |||
use CManifolds, only: InstallIBop, RemoveIBop | |||
use UnitySignalVariables | |||
use UnitySignalsModule, only: Set_Ibop_Install, Set_Ibop_Remove | |||
use UnitySignalsModule, only: Set_Ibop_Install, Set_Ibop_Remove | |||
implicit none | |||
logical , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
@@ -329,11 +322,10 @@ contains | |||
subroutine Set_FillMouseHoleLed(v) | |||
use CDrillingConsoleVariables | |||
use SimulationVariables | |||
use SimulationVariables!, only: FillMouseHoleLedHw => FillMouseHoleLed | |||
use SimulationVariables | |||
! use CMouseHoleEnumVariables | |||
use UnitySignalVariables | |||
use UnitySignalsModule | |||
use UnitySignalsModule | |||
implicit none | |||
logical , intent(in) :: v | |||
#ifdef ExcludeExtraChanges | |||
@@ -63,7 +63,6 @@ INTEGER I | |||
! RAMLINE MINOR LOSSES INPUT | |||
!=========================================================================== | |||
data%State%RamLine%NO_MINORSRAMLINE=34 | |||
ALLOCATE (data%State%BopStackInput%MINORS1(data%State%RamLine%NO_MINORSRAMLINE,4)) | |||
! ID(INCH) LF CV NOTE(BAR) DESCRIPTION | |||
@@ -43,13 +43,15 @@ ALLOCATE (data%State%AirPumpLine%PIPINGS_AIRPUMP(data%State%AirPumpLine%NO_PIPIN | |||
data%State%AirPumpLine%PIPINGS_AIRPUMP(1,1:3)= (/0.5, 60960., 0.03/) !Avg.acc.distance | |||
!60960= 200 ft | |||
ALLOCATE(data%State%AirPumpLine%DIAM_AIR_INCH(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE(data%State%AirPumpLine%Re_air(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE (data%State%AirPumpLine%DIAM_AIR_INCH(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE),data%State%AirPumpLine%Re_air(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE),data%State%AirPumpLine%AREA_AIR(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE), & | |||
data%State%AirPumpLine%LENGT_AIR(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE),data%State%AirPumpLine%ROUGHNESS_AIRPLINE(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE),data%State%AirPumpLine%REL_ROUGHAIR(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE), & | |||
data%State%AirPumpLine%fric_air(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE),data%State%AirPumpLine%fricloss_air(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE(data%State%AirPumpLine%AREA_AIR(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE(data%State%AirPumpLine%LENGT_AIR(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE(data%State%AirPumpLine%ROUGHNESS_AIRPLINE(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE(data%State%AirPumpLine%REL_ROUGHAIR(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE(data%State%AirPumpLine%fric_air(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
ALLOCATE(data%State%AirPumpLine%fricloss_air(data%State%AirPumpLine%NO_PIPINGS_AIRPLINE)) | |||
DO I=1,data%State%AirPumpLine%NO_PIPINGS_AIRPLINE | |||
data%State%AirPumpLine%DIAM_AIR_INCH(I)=data%State%AirPumpLine%PIPINGS_AIRPUMP(I,1) | |||
@@ -76,13 +78,11 @@ data%State%AirPumpLine%MINORS_AIRPUMP(3,1:4)= (/1., 0., 0., 3.4/) | |||
data%State%AirPumpLine%MINORS_AIRPUMP(4,1:4)= (/2., 0., 105., 0./) !valve | |||
data%State%AirPumpLine%MINORS_AIRPUMP(5,1:4)= (/1., 0., 9.2, 0./) !valve | |||
data%State%AirPumpLine%MINORS_AIRPUMP(6,1:4)= (/2., 6.4, 0., 0./) !unionA | |||
ALLOCATE (data%State%AirPumpLine%MINORDIAM_AIR_INCH(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%MINORAREA_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE), & | |||
data%State%AirPumpLine%LF_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%CV_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%NOTE_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE) & | |||
,data%State%AirPumpLine%minlosspa_air(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%minloss_air(data%State%AirPumpLine%NO_MINORS_AIRPLINE)) | |||
ALLOCATE (data%State%AirPumpLine%MINORDIAM_AIR_INCH(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%MINORAREA_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE), & | |||
data%State%AirPumpLine%LF_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%CV_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%NOTE_AIR(data%State%AirPumpLine%NO_MINORS_AIRPLINE) & | |||
,data%State%AirPumpLine%minlosspa_air(data%State%AirPumpLine%NO_MINORS_AIRPLINE),data%State%AirPumpLine%minloss_air(data%State%AirPumpLine%NO_MINORS_AIRPLINE)) | |||
DO I=1,data%State%AirPumpLine%NO_MINORS_AIRPLINE | |||
@@ -6,8 +6,10 @@ subroutine DWFixModeMotion | |||
data%State%Drawworks%Hook_Height_final = data%State%Drawworks%Hook_Height_final ![ft] | |||
data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height_final/3.280839895d0 ![m] | |||
!data%State%Drawworks%Hook_Height_final = data%State%Drawworks%Hook_Height_final ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 0.d0 ![ft/s] | |||
!data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height_final/3.280839895d0 ![m] | |||
data%State%Drawworks%HookLinearVelocity = data%State%Drawworks%HookLinearVelocity_final/3.280839895d0 ![m/s] | |||
data%State%Drawworks%w_drum = 0.d0 | |||
data%State%Drawworks%w_old_drum = 0.d0 | |||
data%State%Drawworks%motion = 0 | |||
@@ -33,17 +33,20 @@ subroutine Drawworks_Direction | |||
data%State%Drawworks%motion = +1 | |||
data%State%Drawworks%w_old_drum = data%State%Drawworks%w_drum !(pi*(data%State%Drawworks%N_old/data%State%Drawworks%Conv_Ratio)/30.d0) ? | |||
data%State%Drawworks%w_drum = (pi*(data%State%Drawworks%Speed/data%State%Drawworks%Conv_Ratio)/30.d0) ![rad/s] | |||
data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height+(((data%State%Drawworks%Diameter/2.0)*(data%State%Drawworks%time_step*0.5d0*(data%State%Drawworks%w_drum+data%State%Drawworks%w_old_drum)))/data%State%Drawworks%NumberOfLine) ![m] | |||
!data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height+(((data%State%Drawworks%Diameter/2.0)*(data%State%Drawworks%time_step*0.5d0*(data%State%Drawworks%w_drum+data%State%Drawworks%w_old_drum)))/data%State%Drawworks%NumberOfLine) ![m] | |||
data%State%Drawworks%HookLinearVelocity = (((data%State%Drawworks%Diameter/2.0)*0.5d0*(data%State%Drawworks%w_drum+data%State%Drawworks%w_old_drum))/data%State%Drawworks%NumberOfLine) ![m/s] | |||
else if ((data%State%Drawworks%Throttle<0.d0) .or. (data%State%Drawworks%Throttle==0.d0 .and. data%State%Drawworks%Speed/=0.d0 .and. data%State%Drawworks%motion==-1)) then !Down | |||
data%State%Drawworks%motion = -1 | |||
data%State%Drawworks%w_old_drum = data%State%Drawworks%w_drum !(pi*(data%State%Drawworks%N_old/data%State%Drawworks%Conv_Ratio)/30.d0) ? | |||
data%State%Drawworks%w_drum = (pi*(data%State%Drawworks%Speed/data%State%Drawworks%Conv_Ratio)/30.d0) ![rad/s] | |||
data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height-(((data%State%Drawworks%Diameter/2.0)*(data%State%Drawworks%time_step*0.5d0*(data%State%Drawworks%w_drum+data%State%Drawworks%w_old_drum)))/data%State%Drawworks%NumberOfLine) ![m] | |||
!data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height-(((data%State%Drawworks%Diameter/2.0)*(data%State%Drawworks%time_step*0.5d0*(data%State%Drawworks%w_drum+data%State%Drawworks%w_old_drum)))/data%State%Drawworks%NumberOfLine) ![m] | |||
data%State%Drawworks%HookLinearVelocity = -(((data%State%Drawworks%Diameter/2.0)*0.5d0*(data%State%Drawworks%w_drum+data%State%Drawworks%w_old_drum))/data%State%Drawworks%NumberOfLine) ![m/s] | |||
else !fixed | |||
data%State%Drawworks%motion = 0 | |||
data%State%Drawworks%w_old_drum = 0.d0 | |||
data%State%Drawworks%w_drum = 0.d0 | |||
data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height | |||
!data%State%Drawworks%HookLinearVelocity = 0.d0 ![m/s] | |||
end if | |||
@@ -28,8 +28,9 @@ subroutine Drawworks_Outputs | |||
Call Activate_FloorCollision() | |||
end if | |||
Call Set_HookHeight( real(data%State%Drawworks%Hook_Height_final) ) ![ft] | |||
!Call Set_HookHeight( real(data%State%Drawworks%Hook_Height_final) ) ![ft] | |||
data%State%Drawworks%TDHookHeight = data%State%Drawworks%Hook_Height_final ![ft] | |||
! = data%State%Drawworks%HookLinearVelocity_final ![ft/s] | |||
!!data%State%Drawworks%HookHeight_graph_output | |||
!data%Equipments%DrillingConsole%ParkingBrakeLed = 0 ! in Drawworks_Inputs | |||
@@ -77,24 +77,25 @@ subroutine Drawworks_Solver | |||
!==================================================== | |||
! Crown Collision (Max_Hook_Height) | |||
!==================================================== | |||
if ( ((3.280839895d0*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
if ( CrownCollision_Status==0 .and. data%State%Drawworks%motion==1 ) then | |||
CrownCollision_Status = 1 | |||
data%State%Drawworks%CrownCollision = .true. | |||
data%State%Drawworks%SoundCrownCollision = .true. | |||
else | |||
data%State%Drawworks%SoundCrownCollision = .false. | |||
end if | |||
if ( data%State%Drawworks%motion==-1 .and. data%State%Drawworks%CrownCollision==.false. ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
! !==================================================== | |||
! ! Crown Collision (Max_Hook_Height) | |||
! !==================================================== | |||
! ?if ( ((3.280839895d0*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
! if ( CrownCollision_Status==0 .and. data%State%Drawworks%motion==1 ) then | |||
! CrownCollision_Status = 1 | |||
! data%State%Drawworks%CrownCollision = .true. | |||
! data%State%Drawworks%SoundCrownCollision = .true. | |||
! else | |||
! data%State%Drawworks%SoundCrownCollision = .false. | |||
! end if | |||
! if ( data%State%Drawworks%motion==-1 .and. data%State%Drawworks%CrownCollision==.false. ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -102,24 +103,25 @@ subroutine Drawworks_Solver | |||
!==================================================== | |||
! Floor Collision (Min_Hook_Height) | |||
!==================================================== | |||
if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
if ( FloorCollision_Status==0 .and. data%State%Drawworks%motion==-1 ) then | |||
FloorCollision_Status = 1 | |||
data%State%Drawworks%FloorCollision = .true. | |||
data%State%Drawworks%SoundFloorCollision = .true. | |||
else | |||
data%State%Drawworks%SoundFloorCollision = .false. | |||
end if | |||
if ( data%State%Drawworks%motion==1 .and. data%State%Drawworks%FloorCollision==.false. ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
! !==================================================== | |||
! ! Floor Collision (Min_Hook_Height) | |||
! !==================================================== | |||
! ?if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
! if ( FloorCollision_Status==0 .and. data%State%Drawworks%motion==-1 ) then | |||
! FloorCollision_Status = 1 | |||
! data%State%Drawworks%FloorCollision = .true. | |||
! data%State%Drawworks%SoundFloorCollision = .true. | |||
! else | |||
! data%State%Drawworks%SoundFloorCollision = .false. | |||
! end if | |||
! if ( data%State%Drawworks%motion==1 .and. data%State%Drawworks%FloorCollision==.false. ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -128,17 +130,18 @@ subroutine Drawworks_Solver | |||
!==================================================== | |||
! Crown Warning | |||
!==================================================== | |||
if ( ((3.280839895*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
if ( data%State%Drawworks%motion==-1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
! !==================================================== | |||
! ! Crown Warning | |||
! !==================================================== | |||
! ?if ( ((3.280839895*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
! if ( data%State%Drawworks%motion==-1 ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -146,17 +149,18 @@ subroutine Drawworks_Solver | |||
!==================================================== | |||
! Floor Warning | |||
!==================================================== | |||
if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
if ( data%State%Drawworks%motion==1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
! !==================================================== | |||
! ! Floor Warning | |||
! !==================================================== | |||
! ?if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
! if ( data%State%Drawworks%motion==1 ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -197,7 +201,8 @@ subroutine Drawworks_Solver | |||
if ( data%State%Drawworks%TDBOPElementNo(j)/=0 ) then | |||
if ( ((data%State%Drawworks%TDBOPHeight(j)-data%State%Drawworks%TDBOPThickness)<=(data%State%Drawworks%TDDrillStemsTopDepth(data%State%Drawworks%TDBOPElementNo(j))+data%State%Drawworks%TDDrillStemsToolJointRange(data%State%Drawworks%TDBOPElementNo(j)))) .and. ((data%State%Drawworks%TDBOPHeight(j)-data%State%Drawworks%TDBOPThickness)>data%State%Drawworks%TDDrillStemsTopDepth(data%State%Drawworks%TDBOPElementNo(j))) .and. (data%State%Drawworks%TDBOPRamDiam(j)<(2.d0*12.d0*data%State%Drawworks%TDDrillStemsRtoolJoint(data%State%Drawworks%TDBOPElementNo(j)))) ) then | |||
if ( data%State%Drawworks%motion==1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
@@ -221,7 +226,8 @@ subroutine Drawworks_Solver | |||
if ( data%State%Drawworks%TDBOPElementNo(j)/=0 ) then | |||
if ( ((data%State%Drawworks%TDBOPHeight(j)+data%State%Drawworks%TDBOPThickness)>=(data%State%Drawworks%TDDrillStemsDownDepth(data%State%Drawworks%TDBOPElementNo(j))-data%State%Drawworks%TDDrillStemsToolJointRange(data%State%Drawworks%TDBOPElementNo(j)))) .and. ((data%State%Drawworks%TDBOPHeight(j)+data%State%Drawworks%TDBOPThickness)<data%State%Drawworks%TDDrillStemsDownDepth(data%State%Drawworks%TDBOPElementNo(j))) .and. (data%State%Drawworks%TDBOPRamDiam(j)<(2.d0*12.d0*data%State%Drawworks%TDDrillStemsRtoolJoint(data%State%Drawworks%TDBOPElementNo(j)))) ) then | |||
if ( data%State%Drawworks%motion==-1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
@@ -241,7 +247,8 @@ subroutine Drawworks_Solver | |||
!==================================================== | |||
if ( (data%State%Drawworks%DriveType==0) .and. (Get_TdsStemIn()) .and. Get_Slips() == SLIPS_SET_END ) then | |||
if ( data%State%Drawworks%motion==1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
@@ -251,7 +258,8 @@ subroutine Drawworks_Solver | |||
!=====> BottomHole ROP Condition | |||
if ( (int(data%State%Drawworks%TDDrillStemBottom*10000.d0)>=(int((data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax)*10000.d0))) .and. (data%State%Drawworks%motion==-1 .or. data%State%Drawworks%motion==0) ) then | |||
if ( data%State%Drawworks%StringIsBottomOfWell==0 ) then | |||
data%State%Drawworks%Hook_Height_final = data%State%Drawworks%Hook_Height_final+(data%State%Drawworks%TDDrillStemBottom-(data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax)) | |||
!?data%State%Drawworks%Hook_Height_final = data%State%Drawworks%Hook_Height_final+(data%State%Drawworks%TDDrillStemBottom-(data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax)) | |||
data%State%Drawworks%HookLinearVelocity_final = (data%State%Drawworks%TDDrillStemBottom-(data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax))/data%State%Drawworks%time_step ![ft/s] | |||
data%State%Drawworks%StringIsBottomOfWell = 1 | |||
end if | |||
Call DWFixModeMotion | |||
@@ -267,7 +275,8 @@ subroutine Drawworks_Solver | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
data%State%Drawworks%HookHeight_graph_output = 0.1189d0*((3.280839895d0*data%State%Drawworks%Hook_Height)-28.d0)-2.6d0 ![ft] | |||
@@ -23,7 +23,8 @@ subroutine Drawworks_Solver_OffMode | |||
data%State%Drawworks%motion = 0 | |||
data%State%Drawworks%w_old_drum = 0.d0 | |||
data%State%Drawworks%w_drum = 0.d0 | |||
data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height | |||
!data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height | |||
data%State%Drawworks%HookLinearVelocity = 0.d0 ![ft/s] | |||
@@ -46,24 +47,25 @@ subroutine Drawworks_Solver_OffMode | |||
!==================================================== | |||
! Crown Collision (Max_Hook_Height) | |||
!==================================================== | |||
if ( ((3.280839895*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
if ( CrownCollision_Status==0 .and. data%State%Drawworks%motion==1 ) then | |||
CrownCollision_Status = 1 | |||
data%State%Drawworks%CrownCollision = .true. | |||
data%State%Drawworks%SoundCrownCollision = .true. | |||
else | |||
data%State%Drawworks%SoundCrownCollision = .false. | |||
end if | |||
if ( data%State%Drawworks%motion==-1 .and. data%State%Drawworks%CrownCollision==.false. ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
!!==================================================== | |||
!! Crown Collision (Max_Hook_Height) | |||
!!==================================================== | |||
! ?if ( ((3.280839895*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
! if ( CrownCollision_Status==0 .and. data%State%Drawworks%motion==1 ) then | |||
! CrownCollision_Status = 1 | |||
! data%State%Drawworks%CrownCollision = .true. | |||
! data%State%Drawworks%SoundCrownCollision = .true. | |||
! else | |||
! data%State%Drawworks%SoundCrownCollision = .false. | |||
! end if | |||
! if ( data%State%Drawworks%motion==-1 .and. data%State%Drawworks%CrownCollision==.false. ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -71,24 +73,25 @@ subroutine Drawworks_Solver_OffMode | |||
!==================================================== | |||
! Floor Collision (Min_Hook_Height) | |||
!==================================================== | |||
if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
if ( FloorCollision_Status==0 .and. data%State%Drawworks%motion==-1 ) then | |||
FloorCollision_Status = 1 | |||
data%State%Drawworks%FloorCollision = .true. | |||
data%State%Drawworks%SoundFloorCollision = .true. | |||
else | |||
data%State%Drawworks%SoundFloorCollision = .false. | |||
end if | |||
if ( data%State%Drawworks%motion==1 .and. data%State%Drawworks%FloorCollision==.false. ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
! !==================================================== | |||
! ! Floor Collision (Min_Hook_Height) | |||
! !==================================================== | |||
! ?if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/3,4,7,10,11,12,14/))) ) then | |||
! if ( FloorCollision_Status==0 .and. data%State%Drawworks%motion==-1 ) then | |||
! FloorCollision_Status = 1 | |||
! data%State%Drawworks%FloorCollision = .true. | |||
! data%State%Drawworks%SoundFloorCollision = .true. | |||
! else | |||
! data%State%Drawworks%SoundFloorCollision = .false. | |||
! end if | |||
! if ( data%State%Drawworks%motion==1 .and. data%State%Drawworks%FloorCollision==.false. ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -97,17 +100,18 @@ subroutine Drawworks_Solver_OffMode | |||
!==================================================== | |||
! Warning (Max_Hook_Height) | |||
!==================================================== | |||
if ( ((3.280839895*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
if ( data%State%Drawworks%motion==-1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
! !==================================================== | |||
! ! Warning (Max_Hook_Height) | |||
! !==================================================== | |||
! ?if ( ((3.280839895*data%State%Drawworks%Hook_Height)>=data%State%Drawworks%max_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
! if ( data%State%Drawworks%motion==-1 ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -115,17 +119,18 @@ subroutine Drawworks_Solver_OffMode | |||
!==================================================== | |||
! Warning (Min_Hook_Height) | |||
!==================================================== | |||
if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
if ( data%State%Drawworks%motion==1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
return | |||
end if | |||
! !==================================================== | |||
! ! Warning (Min_Hook_Height) | |||
! !==================================================== | |||
! ?if ( ((3.280839895*data%State%Drawworks%Hook_Height)<=data%State%Drawworks%min_Hook_Height) .and. (any(data%State%Drawworks%DrillModeCond==(/1,2,5,6,8,9,13/))) ) then | |||
! if ( data%State%Drawworks%motion==1 ) then | |||
! !data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
! data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
! else | |||
! Call DWFixModeMotion | |||
! end if | |||
! return | |||
! end if | |||
@@ -163,7 +168,8 @@ subroutine Drawworks_Solver_OffMode | |||
if ( data%State%Drawworks%TDBOPElementNo(j)/=0 ) then | |||
if ( ((data%State%Drawworks%TDBOPHeight(j)-data%State%Drawworks%TDBOPThickness)<=(data%State%Drawworks%TDDrillStemsTopDepth(data%State%Drawworks%TDBOPElementNo(j))+data%State%Drawworks%TDDrillStemsToolJointRange(data%State%Drawworks%TDBOPElementNo(j)))) .and. ((data%State%Drawworks%TDBOPHeight(j)-data%State%Drawworks%TDBOPThickness)>data%State%Drawworks%TDDrillStemsTopDepth(data%State%Drawworks%TDBOPElementNo(j))) .and. (data%State%Drawworks%TDBOPRamDiam(j)<(2.d0*12.d0*data%State%Drawworks%TDDrillStemsRtoolJoint(data%State%Drawworks%TDBOPElementNo(j)))) ) then | |||
if ( data%State%Drawworks%motion==1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
@@ -187,7 +193,8 @@ subroutine Drawworks_Solver_OffMode | |||
if ( data%State%Drawworks%TDBOPElementNo(j)/=0 ) then | |||
if ( ((data%State%Drawworks%TDBOPHeight(j)+data%State%Drawworks%TDBOPThickness)>=(data%State%Drawworks%TDDrillStemsDownDepth(data%State%Drawworks%TDBOPElementNo(j))-data%State%Drawworks%TDDrillStemsToolJointRange(data%State%Drawworks%TDBOPElementNo(j)))) .and. ((data%State%Drawworks%TDBOPHeight(j)+data%State%Drawworks%TDBOPThickness)<data%State%Drawworks%TDDrillStemsDownDepth(data%State%Drawworks%TDBOPElementNo(j))) .and. (data%State%Drawworks%TDBOPRamDiam(j)<(2.d0*12.d0*data%State%Drawworks%TDDrillStemsRtoolJoint(data%State%Drawworks%TDBOPElementNo(j)))) ) then | |||
if ( data%State%Drawworks%motion==-1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
@@ -207,7 +214,8 @@ subroutine Drawworks_Solver_OffMode | |||
!==================================================== | |||
if ( (data%State%Drawworks%DriveType==0) .and. (Get_TdsStemIn()) .and. Get_Slips() == SLIPS_SET_END ) then | |||
if ( data%State%Drawworks%motion==1 ) then | |||
data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
else | |||
Call DWFixModeMotion | |||
end if | |||
@@ -224,7 +232,8 @@ subroutine Drawworks_Solver_OffMode | |||
!=====> BottomHole ROP Condition | |||
if ( (int(data%State%Drawworks%TDDrillStemBottom*10000.d0)>=(int((data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax)*10000.d0))) .and. (data%State%Drawworks%motion==-1 .or. data%State%Drawworks%motion==0) ) then | |||
if ( data%State%Drawworks%StringIsBottomOfWell==0 ) then | |||
data%State%Drawworks%Hook_Height_final = data%State%Drawworks%Hook_Height_final+(data%State%Drawworks%TDDrillStemBottom-(data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax)) | |||
!?data%State%Drawworks%Hook_Height_final = data%State%Drawworks%Hook_Height_final+(data%State%Drawworks%TDDrillStemBottom-(data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax)) | |||
data%State%Drawworks%HookLinearVelocity_final = (data%State%Drawworks%TDDrillStemBottom-(data%State%Drawworks%TDWellTotalLength+data%State%Drawworks%TDDlMax))/data%State%Drawworks%time_step ![ft/s] | |||
data%State%Drawworks%StringIsBottomOfWell = 1 | |||
end if | |||
Call DWFixModeMotion | |||
@@ -238,7 +247,8 @@ subroutine Drawworks_Solver_OffMode | |||
data%State%Drawworks%Hook_Height_final=3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
!data%State%Drawworks%Hook_Height_final=3.280839895d0*data%State%Drawworks%Hook_Height ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 3.280839895d0*data%State%Drawworks%HookLinearVelocity ![ft/s] | |||
data%State%Drawworks%HookHeight_graph_output=0.1189d0*((3.280839895d0*data%State%Drawworks%Hook_Height)-28.0d0)-2.6d0 ![ft] | |||
@@ -20,9 +20,11 @@ subroutine Drawworks_StartUp | |||
data%State%Drawworks%Hook_Height_ini = 75.0d0 ![ft] | |||
data%State%Drawworks%Hook_Height_ini_graph_output = -1.54090d0 ![ft] | |||
data%State%Drawworks%Hook_Height_inim = 0.3048d0*data%State%Drawworks%Hook_Height_ini ![m] | |||
data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height_inim ![m] | |||
data%State%Drawworks%Hook_Height_final = 75.d0 ![ft] | |||
data%State%Drawworks%TDHookHeight = 75.d0 ![ft] | |||
!data%State%Drawworks%Hook_Height = data%State%Drawworks%Hook_Height_inim ![m] | |||
!data%State%Drawworks%Hook_Height_final = 75.d0 ![ft] | |||
data%State%Drawworks%TDHookHeight = data%State%Drawworks%Hook_Height_final ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 0.d0 ![ft/s] | |||
data%State%Drawworks%HookLinearVelocity = 0.d0 ![m/s] | |||
@@ -26,6 +26,8 @@ MODULE Drawworks_VARIABLES | |||
REAL :: Hook_Height, Hook_Height_ini, Hook_Height_inim, Hook_Height_ini_graph_output, Hook_Height_final, max_Hook_Height, min_Hook_Height, HookHeight_graph_output | |||
REAL :: N_Throtle, Conv_Ratio, NumberOfLine, Speed, N_new, N_old ! N[RPM] | |||
REAL :: w_drum, w_old_drum ! w[rad/s] | |||
REAL :: HookLinearVelocity ! [m/s] | |||
REAL :: HookLinearVelocity_final ! [ft/s] | |||
REAL , Dimension(6) :: TDBOPHeight | |||
REAL , Dimension(4) :: TDBOPRamDiam | |||
REAL :: TDBOPThickness, TDDrillStemBottom, TDWellTotalLength, TDDlMax | |||
@@ -27,6 +27,7 @@ MODULE Drawworks_VARIABLES | |||
REAL :: Hook_Height, Hook_Height_ini, Hook_Height_inim, Hook_Height_ini_graph_output, Hook_Height_final, max_Hook_Height, min_Hook_Height, HookHeight_graph_output | |||
REAL :: N_Throtle, Conv_Ratio, NumberOfLine, Speed, N_new, N_old ! N[RPM] | |||
REAL :: w_drum, w_old_drum ! w[rad/s] | |||
REAL :: HookLinearVelocity ! [ft/s] | |||
REAL , Dimension(6) :: TDBOPHeight | |||
REAL , Dimension(4) :: TDBOPRamDiam | |||
REAL :: TDBOPThickness, TDDrillStemBottom, TDWellTotalLength, TDDlMax | |||
@@ -26,11 +26,11 @@ subroutine DisconnectingPipe ! is called in subroutine CirculationCodeSelect | |||
! ======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 (Get_KellyConnection() == KELLY_CONNECTION_NOTHING .and. data%state%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 | |||
if ( data%state%manifold%Valve(53)%Status == .true. ) then | |||
data%State%MudSystem%MudBucketVolume= ExcessMudVolume | |||
else | |||
data%State%MudSystem%MudBucketVolume= 0.0 | |||
@@ -801,16 +801,16 @@ use SimulationVariables !@ | |||
data%State%FricPressDrop%PumpToManifoldCompressedMudVol = data%State%FricPressDrop%PumpToManifoldCompressedMudVol + MP1_Q / ConvMinToSec * dt | |||
PumpPressure1= data%State%FricPressDrop%PumpToManifoldCompressedMudVol / (MudCompressibility * data%State%FricPressDrop%PumpToManifoldMudVol) | |||
write(*,*) '21)PumpPressure1=' , PumpPressure1 | |||
WRITE (*,*) ' valve 1 ', Manifold%Valve(1)%Status | |||
WRITE (*,*) ' valve 4 ', Manifold%Valve(4)%Status | |||
WRITE (*,*) ' valve 6 ', Manifold%Valve(6)%Status | |||
WRITE (*,*) ' valve 7 ', Manifold%Valve(7)%Status | |||
WRITE (*,*) ' valve 8 ', Manifold%Valve(8)%Status | |||
WRITE (*,*) ' valve 9 ', Manifold%Valve(9)%Status | |||
WRITE (*,*) ' valve 13 ', Manifold%Valve(13)%Status | |||
WRITE (*,*) ' valve 68 ', Manifold%Valve(68)%Status | |||
WRITE (*,*) ' valve 69 ', Manifold%Valve(69)%Status | |||
WRITE (*,*) ' valve 48 ', Manifold%Valve(48)%Status | |||
WRITE (*,*) ' valve 1 ', data%state%manifold%Valve(1)%Status | |||
WRITE (*,*) ' valve 4 ', data%state%manifold%Valve(4)%Status | |||
WRITE (*,*) ' valve 6 ', data%state%manifold%Valve(6)%Status | |||
WRITE (*,*) ' valve 7 ', data%state%manifold%Valve(7)%Status | |||
WRITE (*,*) ' valve 8 ', data%state%manifold%Valve(8)%Status | |||
WRITE (*,*) ' valve 9 ', data%state%manifold%Valve(9)%Status | |||
WRITE (*,*) ' valve 13 ', data%state%manifold%Valve(13)%Status | |||
WRITE (*,*) ' valve 68 ', data%state%manifold%Valve(68)%Status | |||
WRITE (*,*) ' valve 69 ', data%state%manifold%Valve(69)%Status | |||
WRITE (*,*) ' valve 48 ', data%state%manifold%Valve(48)%Status | |||
!call DisplayOpenPathsWrite() | |||
ENDIF | |||
@@ -818,16 +818,16 @@ use SimulationVariables !@ | |||
data%State%FricPressDrop%PumpToManifoldCompressedMudVol = data%State%FricPressDrop%PumpToManifoldCompressedMudVol + MP2_Q / ConvMinToSec * dt | |||
PumpPressure2= data%State%FricPressDrop%PumpToManifoldCompressedMudVol / (MudCompressibility * data%State%FricPressDrop%PumpToManifoldMudVol) | |||
write(*,*) '22)PumpPressure1=' , PumpPressure2 | |||
WRITE (*,*) ' -valve 1 ', Manifold%Valve(1)%Status | |||
WRITE (*,*) ' -valve 4 ', Manifold%Valve(4)%Status | |||
WRITE (*,*) ' -valve 6 ', Manifold%Valve(6)%Status | |||
WRITE (*,*) ' -valve 7 ', Manifold%Valve(7)%Status | |||
WRITE (*,*) ' -valve 8 ', Manifold%Valve(8)%Status | |||
WRITE (*,*) ' -valve 9 ', Manifold%Valve(9)%Status | |||
WRITE (*,*) ' -valve 13 ', Manifold%Valve(13)%Status | |||
WRITE (*,*) ' -valve 68 ', Manifold%Valve(68)%Status | |||
WRITE (*,*) ' -valve 69 ', Manifold%Valve(69)%Status | |||
WRITE (*,*) ' -valve 48 ', Manifold%Valve(48)%Status | |||
WRITE (*,*) ' -valve 1 ', data%state%manifold%Valve(1)%Status | |||
WRITE (*,*) ' -valve 4 ', data%state%manifold%Valve(4)%Status | |||
WRITE (*,*) ' -valve 6 ', data%state%manifold%Valve(6)%Status | |||
WRITE (*,*) ' -valve 7 ', data%state%manifold%Valve(7)%Status | |||
WRITE (*,*) ' -valve 8 ', data%state%manifold%Valve(8)%Status | |||
WRITE (*,*) ' -valve 9 ', data%state%manifold%Valve(9)%Status | |||
WRITE (*,*) ' -valve 13 ', data%state%manifold%Valve(13)%Status | |||
WRITE (*,*) ' -valve 68 ', data%state%manifold%Valve(68)%Status | |||
WRITE (*,*) ' -valve 69 ', data%state%manifold%Valve(69)%Status | |||
WRITE (*,*) ' -valve 48 ', data%state%manifold%Valve(48)%Status | |||
!call DisplayOpenPathsWrites() | |||
ENDIF | |||
@@ -1996,9 +1996,9 @@ use SimulationVariables !@ | |||
!!====================================================================== | |||
IF (Manifold%Valve(65)%Status == .TRUE.) call Activate_Pump1PopOffValveBlown() !Pump1PopOffValveBlown= .TRUE. | |||
IF (Manifold%Valve(66)%Status == .TRUE.) call Activate_Pump2PopOffValveBlown() ! Pump2PopOffValveBlown= .TRUE. | |||
IF (Manifold%Valve(67)%Status == .TRUE.) call Activate_Pump3PopOffValveBlown() !Pump2PopOffValveBlown= .TRUE. | |||
IF (data%state%manifold%Valve(65)%Status == .TRUE.) call Activate_Pump1PopOffValveBlown() !Pump1PopOffValveBlown= .TRUE. | |||
IF (data%state%manifold%Valve(66)%Status == .TRUE.) call Activate_Pump2PopOffValveBlown() ! Pump2PopOffValveBlown= .TRUE. | |||
IF (data%state%manifold%Valve(67)%Status == .TRUE.) call Activate_Pump3PopOffValveBlown() !Pump2PopOffValveBlown= .TRUE. | |||
IF (data%State%MudSystem%ActiveTankVolume >= (data%Configuration%Mud%ActiveTotalTankCapacityGal-data%Configuration%Mud%ActiveSettledContentsGal)) THEN | |||
@@ -2806,7 +2806,7 @@ use SimulationVariables !@ | |||
!============BellNippleToPits-FullWell(MLnumber=3)============== | |||
if ( Manifold%Valve(41)%Status == .false. .and. Manifold%Valve(42)%Status == .false. ) then | |||
if ( data%state%manifold%Valve(41)%Status == .false. .and. data%state%manifold%Valve(42)%Status == .false. ) then | |||
call ChangeValve(60, .TRUE.) | |||
else | |||
call ChangeValve(60, .FALSE.) | |||
@@ -32,9 +32,9 @@ module MudSystemMain | |||
implicit none | |||
!if(print_log) print* , 'MudSystem_Step' | |||
!CALL main | |||
if(Manifold%IsTraverse) then | |||
if(data%state%manifold%IsTraverse) then | |||
call LineupAndPath() | |||
Manifold%IsTraverse = .false. | |||
data%state%manifold%IsTraverse = .false. | |||
endif | |||
call main() | |||
end subroutine MudSystem_Step | |||
@@ -1633,7 +1633,7 @@ use SimulationVariables !@@@ | |||
WRITE (*,*) 'WellToChokeManifoldOpen', data%State%MudSystem%WellToChokeManifoldOpen | |||
else | |||
data%State%MudSystem%SoundGasThroughChoke = 0 | |||
if(print_log) print* , 'SoundGasThroughChoke2=', data%State%MudSystem%SoundGasThroughChoke | |||
! if(print_log) print* , 'SoundGasThroughChoke2=', data%State%MudSystem%SoundGasThroughChoke | |||
endif | |||
!if(print_log) print* , 'SoundGasThroughChoke3=', SoundGasThroughChoke | |||
@@ -73,17 +73,17 @@ IF (KickVARIABLES%WellHeadOpen .OR. KickVARIABLES%NoGasPocket == 0) THEN !! ( | |||
WRITE (*,*) ' PressureGauges(2) , Kchoke' , data%State%PressureDisplay%PressureGauges(2) , data%State%FricPressDrop%Kchoke | |||
WRITE (*,*) 'Initial guess after opening choke =', GasPocketFlowInduced%Array(1) | |||
WRITE (*,*) ' valve 49 ', Manifold%Valve(49)%Status | |||
WRITE (*,*) ' valve 47 ', Manifold%Valve(47)%Status | |||
WRITE (*,*) ' valve 26 ', Manifold%Valve(26)%Status | |||
WRITE (*,*) ' valve 30 ', Manifold%Valve(30)%Status | |||
WRITE (*,*) ' valve 34 ', Manifold%Valve(34)%Status | |||
WRITE (*,*) ' valve 63 ', Manifold%Valve(63)%Status | |||
WRITE (*,*) ' valve 28 ', Manifold%Valve(28)%Status | |||
WRITE (*,*) ' valve 33 ', Manifold%Valve(33)%Status | |||
WRITE (*,*) ' valve 62 ', Manifold%Valve(62)%Status | |||
WRITE (*,*) ' valve 36 ', Manifold%Valve(36)%Status | |||
WRITE (*,*) ' valve 38 ', Manifold%Valve(38)%Status | |||
WRITE (*,*) ' valve 49 ', data%state%manifold%Valve(49)%Status | |||
WRITE (*,*) ' valve 47 ', data%state%manifold%Valve(47)%Status | |||
WRITE (*,*) ' valve 26 ', data%state%manifold%Valve(26)%Status | |||
WRITE (*,*) ' valve 30 ', data%state%manifold%Valve(30)%Status | |||
WRITE (*,*) ' valve 34 ', data%state%manifold%Valve(34)%Status | |||
WRITE (*,*) ' valve 63 ', data%state%manifold%Valve(63)%Status | |||
WRITE (*,*) ' valve 28 ', data%state%manifold%Valve(28)%Status | |||
WRITE (*,*) ' valve 33 ', data%state%manifold%Valve(33)%Status | |||
WRITE (*,*) ' valve 62 ', data%state%manifold%Valve(62)%Status | |||
WRITE (*,*) ' valve 36 ', data%state%manifold%Valve(36)%Status | |||
WRITE (*,*) ' valve 38 ', data%state%manifold%Valve(38)%Status | |||
ELSE ! flow through bell nipple | |||
k = data%State%FricPressDrop%NoHorizontalEl + data%State%FricPressDrop%NoStringEl + data%State%FricPressDrop%NoAnnulusEl | |||
@@ -38,7 +38,7 @@ module FluidFlowMain | |||
FlowDuration = 3600000 * (FlowEndTime(5) - FlowStartTime(5)) + 60000 * (FlowEndTime(6) - FlowStartTime(6)) + 1000 * (FlowEndTime(7) - FlowStartTime(7)) + (FlowEndTime(8) - FlowStartTime(8)) | |||
if(print_log) WRITE (*,*) 'FlowDuration (ms)=' , FlowDuration | |||
! if(print_log) WRITE (*,*) 'FlowDuration (ms)=' , FlowDuration | |||
end subroutine FluidFlow_Step | |||
@@ -6,7 +6,7 @@ subroutine Fluid_Flow_Solver | |||
use PressureDisplayVARIABLESModule | |||
USE FricPressDropVarsModule | |||
USE MudSystemVARIABLES | |||
use SimulationVariables !@@@ | |||
use SimulationVariables !@@@ | |||
USE Fluid_Flow_Startup_Vars | |||
USE CError | |||
@@ -6,7 +6,7 @@ MODULE KickVARIABLESModule | |||
IMPLICIT NONE | |||
TYPE :: KickVARIABLESTYPE | |||
! TYPE :: KickVARIABLESTYPE | |||
REAL :: DrillStringSpeed ! drill string speed during surge and swab [ft/s] | |||
@@ -80,8 +80,8 @@ MODULE KickVARIABLESModule | |||
END TYPE KickVARIABLESTYPE | |||
TYPE(KickVARIABLESTYPE) :: KickVARIABLES | |||
! END TYPE KickVARIABLESTYPE | |||
! TYPE(KickVARIABLESTYPE) :: KickVARIABLES | |||
INTEGER :: KickIteration ! the number of itertion for calculating pressure and flowrate, when kick is in the well | |||
@@ -152,6 +152,9 @@ SRCS_F =\ | |||
Equipments/MudSystem/MudSystem_Variables.f90 \ | |||
TorqueDrag/TD_Modules/TD_DrillStem.f90 \ | |||
CSharp/Equipments/MudPathFinding/CStack.f90 \ | |||
\ | |||
CSharp/Equipments/MudPathFinding/ManifoldVariables.f90 \ | |||
\ | |||
CSharp/Problems/CDrillStemProblemsVariables.f90 \ | |||
CSharp/Problems/COtherProblemsVariables.f90 \ | |||
CSharp/Problems/CLostProblemsVariables.f90 \ | |||
@@ -120,9 +120,9 @@ Module RedisInterface | |||
use iso_c_binding, only: c_null_char | |||
character(len=*):: str | |||
character(len=len_trim(str)+1)::c_str | |||
print *, "publishMessageToChannel: ", str | |||
if(str .ne. 'ack') print *, "publishMessageToChannel: ", str | |||
c_str = str//c_null_char | |||
if(log_level>4) print *,"Sending message: ",len_trim(str) | |||
! if(log_level>4) print *,"Sending message: ",len_trim(str) | |||
call publishMessageToChannel_C(c_str) | |||
end subroutine publishMessageToChannel | |||
@@ -12,14 +12,13 @@ char *result,*key,*pass,*channel_in,*channel_out; | |||
extern void test(); | |||
extern void setTongLever(int *v); | |||
extern void ButtonPress_Slips(); | |||
extern void ToggleValve(int *valve_number); | |||
void addnums( int* a, int* b ) | |||
char *clone(char *s) | |||
{ | |||
int c = (*a) + (*b); /* convert pointers to values, then add them */ | |||
printf("sum of %i and %i is %i\n", (*a), (*b), c ); | |||
} | |||
char *r = malloc(strlen(s)+1); | |||
} | |||
void initConnection(char *address, int *port,char * password,char *datakey,int *returnValue) | |||
{ | |||
context = redisConnect(address,*port); | |||
@@ -77,15 +76,6 @@ void setData(char *part, char *data) | |||
freeReplyObject(reply); | |||
} | |||
// void getData_bystr(void *s) | |||
// { | |||
// redisReply *reply; | |||
// reply = redisCommand(context, "GET %s.in",key); | |||
// freeReplyObject(reply); | |||
// set_fortran_string(s, strlen(reply->str), reply->str); | |||
// return; | |||
// } | |||
char *getData(int *len) | |||
{ | |||
@@ -120,7 +110,13 @@ void onMessage(redisAsyncContext * c, void *reply, void * privdata) { | |||
if(strcmp(r->element[0]->str,"message")==0) | |||
if(strcmp(r->element[1]->str,channel_in)==0) | |||
{ | |||
char *fn = r->element[2]->str; | |||
// char *message = malloc(srlen(r->element[2]->str)); | |||
// strcpy(message,r->element[2]->str); | |||
char delimiter = ','; | |||
char *chptr = strchr(r->element[2]->str, delimiter); | |||
char *fn = strtok(r->element[2]->str,&delimiter); | |||
char *parameter = malloc(20); | |||
parameter = strtok(NULL,&delimiter); | |||
printf("calling %s\n",fn); | |||
if(strcmp(fn,"test")==0) | |||
test(); | |||
@@ -133,8 +129,14 @@ void onMessage(redisAsyncContext * c, void *reply, void * privdata) { | |||
setTongLever(&v); | |||
}else if(strcmp(fn,"BUTTON_PRESS_SLIPS")==0){ | |||
ButtonPress_Slips(); | |||
} | |||
else | |||
}else if(strcmp(fn,"ChangeValve")==0){ | |||
int valve_number = atoi(parameter); | |||
ToggleValve(&valve_number); | |||
// }else if(strcmp(fn,"KellyConnected")==0){ | |||
// KellyConnected(); | |||
// }else if(strcmp(fn,"KellyDisconnected")==0){ | |||
// KellyDisconnected(); | |||
}else | |||
printf("message: %s\n",r->element[2]->str); | |||
} | |||
} | |||
@@ -0,0 +1,23 @@ | |||
#include <string.h> | |||
#include <stdio.h> | |||
#include <stdlib.h> | |||
int main () { | |||
// char str[80] = "This is - www.tutorialspoint.com - website"; | |||
char *str=malloc(30); | |||
scanf("%s",str); | |||
const char s[2] = "-"; | |||
char *token; | |||
/* get the first token */ | |||
token = strtok(str, s); | |||
/* walk through other tokens */ | |||
while( token != NULL ) { | |||
printf( " %s\n", token ); | |||
token = strtok(NULL, s); | |||
} | |||
return(0); | |||
} |
@@ -2,7 +2,8 @@ module SimulationVariables | |||
use Constants | |||
use logging | |||
use json_module | |||
use ManifoldVariables | |||
use CUnityInputs | |||
use CUnityOutputs | |||
use COperationScenariosVariables | |||
@@ -109,6 +110,7 @@ module SimulationVariables | |||
end type EquipmentControlType | |||
type SimulationStateType | |||
type(ManifoldType)::Manifold | |||
! Type(HoistingType)::Hoisting !This ds placed twice in data (onece in configuration, once in state) | |||
type(OperationScenarioType)::OperationScenario | |||
type(NotificationType)::notifications | |||
@@ -119,10 +119,11 @@ module Simulator | |||
do while (.true.) | |||
if(mod(simulationStep,print_freq)==0) then | |||
print_log=.true. | |||
! call publishMessageToChannel("Hello from FORTRAN!") | |||
else | |||
print_log=.false. | |||
endif | |||
endif | |||
if(mod(simulationStep,10)==0) call publishMessageToChannel("ack") | |||
if(simulationStep>100) exit | |||
t0 = time_ms() | |||
if(print_log) print *,"simulationStep = ",simulationStep | |||
call read_variables() | |||
@@ -258,6 +259,7 @@ module Simulator | |||
call WarningsToJson(jsonroot) | |||
! call ProblemsToJson(jsonroot) | |||
call EquipmentsToJson(jsonroot) | |||
call StateToJson(jsonroot) | |||
call jsoncore%print_to_string(jsonroot,redisInput) | |||
if(log_level>4) then | |||
@@ -312,9 +314,9 @@ module Simulator | |||
logical::found | |||
call getData(redisOutput,leng) | |||
open(1,file="redisContent.json",status="REPLACE") | |||
write(1,"(A)") redisOutput | |||
close(1) | |||
! open(1,file="redisContent.json",status="REPLACE") | |||
! write(1,"(A)") redisOutput | |||
! close(1) | |||
call jsonfile%initialize() | |||
call jsonfile%get_core(json) | |||
! print *,"len_trim(redidOutput)=",len_trim(redisOutput) | |||
@@ -325,6 +327,7 @@ module Simulator | |||
call json%get(jsonroot,'status',pval) | |||
call json%get(pval,stat) | |||
if (stat==0) then | |||
if(print_log) print *,"Status is oddly zero" | |||
return | |||
endif | |||
simulationStatus = stat | |||
@@ -403,12 +406,17 @@ module Simulator | |||
call ChokeManifoldFromJson(p) | |||
call DataDisplayConsoleFromJson(p) | |||
call DrillingConsoleFromJson(jsonfile) | |||
! call HookFromJson(p) | |||
call StandPipeManifoldFromJson(p) | |||
call TopDrivePanelFromJson(p) | |||
! call DrillingWatchFromJson(p) | |||
call TankFromJson(p) | |||
call UnityInputsFromJson(jsonfile) | |||
! call HookFromJson(p) | |||
call jsonfile%get('Equipments.HookHeight',data%State%Drawworks%Hook_Height_final,is_found) | |||
if ( .not. is_found ) call logg(4,"Not found: Equipments.HookHeight") | |||
if(print_log) print *,"HookHeight=",data%State%Drawworks%Hook_Height_final | |||
end subroutine | |||
subroutine EquipmentsToJson(parent) | |||
@@ -426,11 +434,12 @@ module Simulator | |||
call ChokeManifoldToJson(p) | |||
call DataDisplayConsoleToJson(p) | |||
call DrillingConsoleToJson(p) | |||
call HookToJson(p) | |||
call StandPipeManifoldToJson(p) | |||
call TopDrivePanelToJson(p) | |||
call DrillingWatchToJson(p) | |||
! call TankToJson(p) | |||
! call HookToJson(p) | |||
call jsoncore%add(p,"HookVelocity",data%State%Drawworks%HookLinearVelocity_final) | |||
! 3. add new node to parent | |||
call jsoncore%add(parent,p) | |||
@@ -536,9 +545,10 @@ module Simulator | |||
! 1. create new node | |||
call jsoncore%create_object(p,'State') | |||
call ManifoldToJson(p) | |||
! call OperationScenarioToJson(p) | |||
call notificationsToJson(p) | |||
! call permissionsToJson(p) | |||
! call unitySignalsToJson(p) | |||
! call StudentStationToJson(p) | |||
@@ -603,16 +613,11 @@ module Simulator | |||
!use this as a template | |||
subroutine notificationsToJson(parent) | |||
type(json_value),pointer :: parent | |||
type(json_value),pointer :: p | |||
! 1. create new node | |||
call jsoncore%create_object(p,'Notifications') | |||
! 2. add member of data type to new node | |||
! 3. add new node to parent | |||
call jsoncore%add(parent,p) | |||
end subroutine | |||
@@ -49,9 +49,11 @@ subroutine TD_StartUp | |||
data%State%TD_BOP%AnnularFillingFinal = 0.d0 | |||
data%State%Drawworks%TDHookHeight = 75.d0 ![ft] | |||
data%State%Drawworks%Hook_Height_ini = 75.d0 ![ft] | |||
data%State%Drawworks%Hook_Height_final = 75.d0 ![ft] | |||
!data%State%Drawworks%Hook_Height_final = 75.d0 ![ft] | |||
data%State%Drawworks%HookLinearVelocity_final = 0.d0 ![ft/s] | |||
data%State%Drawworks%TDHookHeight = data%State%Drawworks%Hook_Height_final ![ft] | |||
@@ -0,0 +1,316 @@ | |||
allocate string | |||
connection initialized | |||
initializing modules | |||
pump1 initialized | |||
RT initialized | |||
TD initialized | |||
time step delay 4 18 10 | |||
KellyDisconnected() | |||
Modules are initialized | |||
modules initialized | |||
ListenToChannel | |||
simulationStep = 1 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 1402 | |||
simulationStep = 2 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 242 | |||
simulationStep = 3 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 321 | |||
simulationStep = 4 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 185 | |||
simulationStep = 5 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 212 | |||
simulationStep = 6 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 165 | |||
simulationStep = 7 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 284 | |||
simulationStep = 8 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 272 | |||
simulationStep = 9 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 208 | |||
simulationStep = 10 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 190 | |||
simulationStep = 11 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 170 | |||
simulationStep = 12 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 188 | |||
simulationStep = 13 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 176 | |||
simulationStep = 14 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 158 | |||
simulationStep = 15 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 16 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 149 | |||
simulationStep = 17 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 149 | |||
simulationStep = 18 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 19 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 150 | |||
simulationStep = 20 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 142 | |||
simulationStep = 21 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 22 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 151 | |||
simulationStep = 23 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 24 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 150 | |||
simulationStep = 25 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 26 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 27 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 28 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 29 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 30 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 31 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 141 | |||
simulationStep = 32 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 144 | |||
simulationStep = 33 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 150 | |||
simulationStep = 34 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 35 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 36 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 37 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 152 | |||
simulationStep = 38 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 39 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 144 | |||
simulationStep = 40 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 142 | |||
simulationStep = 41 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 42 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 43 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 44 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 143 | |||
simulationStep = 45 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 46 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 144 | |||
simulationStep = 47 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 48 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 49 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 50 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 51 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 52 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 53 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 154 | |||
simulationStep = 54 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 142 | |||
simulationStep = 55 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 56 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 57 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 58 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 59 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 60 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 141 | |||
simulationStep = 61 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 62 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 63 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 64 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 65 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 66 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 150 | |||
simulationStep = 67 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 68 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 69 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 161 | |||
simulationStep = 70 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 162 | |||
simulationStep = 71 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 72 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 149 | |||
simulationStep = 73 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 74 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 149 | |||
simulationStep = 75 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 152 | |||
simulationStep = 76 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 146 | |||
simulationStep = 77 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 262 | |||
simulationStep = 78 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 173 | |||
simulationStep = 79 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 172 | |||
simulationStep = 80 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 176 | |||
simulationStep = 81 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 178 | |||
simulationStep = 82 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 255 | |||
simulationStep = 83 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 179 | |||
simulationStep = 84 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 174 | |||
simulationStep = 85 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 180 | |||
simulationStep = 86 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 164 | |||
simulationStep = 87 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 88 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 149 | |||
simulationStep = 89 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 144 | |||
simulationStep = 90 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 154 | |||
simulationStep = 91 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 152 | |||
simulationStep = 92 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 93 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
simulationStep = 94 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 145 | |||
simulationStep = 95 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 152 | |||
simulationStep = 96 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 150 | |||
simulationStep = 97 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 149 | |||
simulationStep = 98 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 149 | |||
simulationStep = 99 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 148 | |||
simulationStep = 100 | |||
HookHeight= 10.67848 | |||
Simulation step can not be complete in 100 ms. step time= 147 | |||
Connection Stablished to 78.109.201.86 | |||
Authentication is done. | |||
Listening To channel (C) | |||
Subscribed to channel 37364875-c9cf-43a3-de45-08dc0c6103c9.ch_in | |||
got a message of type: 2 |