|
- module CHook
- use CHookVariables
- use SimulationVariables
- implicit none
- public
- contains
-
- 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%EquipmentControl%Hook%HookHeight_S)
- call json%add(p,"HookHeight",data%EquipmentControl%Hook%HookHeight)
-
- call json%add(parent,p)
- end subroutine
-
- subroutine Set_HookHeight(v)
- use CDrillingConsoleVariables
- use SimulationVariables
- use SimulationVariables
- implicit none
- real , intent(in) :: v
-
- #ifdef ExcludeExtraChanges
- if(data%EquipmentControl%Hook%HookHeight == v) return
- #endif
- data%EquipmentControl%Hook%HookHeight = v
-
- ! if(associated(HookHeightPtr)) then
- ! call HookHeightPtr(data%EquipmentControl%Hook%HookHeight)
- ! end if
-
- #ifdef deb
- print*, 'HookHeight=', data%EquipmentControl%Hook%HookHeight
- #endif
-
- !**call data%EquipmentControl%Hook%OnHookHeightChange%RunAll(data%EquipmentControl%Hook%HookHeight)
- end subroutine
-
-
- subroutine Set_HookHeight_S(v)
- implicit none
- real , intent(in) :: v
-
- if(v == data%EquipmentControl%Hook%HookHeight) then
- return
- elseif (v > data%EquipmentControl%Hook%HookHeight) then
- loop1: do
- call Set_HookHeight(data%EquipmentControl%Hook%HookHeight + 0.2)
- if(abs(v - data%EquipmentControl%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%EquipmentControl%Hook%HookHeight - 0.2)
- if(abs(data%EquipmentControl%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%EquipmentControl%Hook%HookHeight_S)
- end subroutine
- end module CHook
|