|
1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374 |
- module CHook
- use CHookVariables
- use SimulationVariables
- implicit none
- public
- contains
-
- ! subroutine HookFromJson(jsonfile)
- ! type(json_file)::jsonfile
- ! logical::found
-
- ! 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
-
- ! 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,"Velocity",data%State%Drawworks%HookLinearVelocity_final)
- ! call json%add(parent,p)
- ! end subroutine
-
- subroutine Set_HookHeight(v)
- use CDrillingConsoleVariables
- use SimulationVariables
- implicit none
- real , intent(in) :: v
- data%Equipments%Hook%HookHeight = v
-
- ! if(associated(HookHeightPtr)) then
- ! call HookHeightPtr(data%Equipments%Hook%HookHeight)
- ! end if
-
- !**call data%Equipments%Hook%OnHookHeightChange%RunAll(data%Equipments%Hook%HookHeight)
- end subroutine
-
-
- subroutine Set_HookHeight_S(v)
- implicit none
- real , intent(in) :: v
-
- if(v == data%Equipments%Hook%HookHeight) then
- return
- elseif (v > data%Equipments%Hook%HookHeight) then
- loop1: do
- call Set_HookHeight(data%Equipments%Hook%HookHeight + 0.2)
- if(abs(v - data%Equipments%Hook%HookHeight) <= 0.1) then
- call Set_HookHeight(v)
- exit loop1
- endif
- call sleepqq(100)
- enddo loop1
- else ! v < HookHeight
- loop2: do
- call Set_HookHeight(data%Equipments%Hook%HookHeight - 0.2)
- if(abs(data%Equipments%Hook%HookHeight - v) <= 0.1) then
- call Set_HookHeight(v)
- exit loop2
- endif
- call sleepqq(100)
- enddo loop2
- endif
-
- end subroutine
-
- subroutine Update_HookHeight_From_Snapshot()
- implicit none
- call Set_HookHeight_S(data%Equipments%Hook%HookHeight_S)
- end subroutine
- end module CHook
|