sig
  type dWorldID
  type dSpaceID
  type dBodyID
  type 'a dGeomID
  type dJointID
  type dJointGroupID
  type dMass
  type dVector3 = { x : float; y : float; z : float; w : float; }
  type dVector4 = Ode.LowLevel.dVector3
  type dMatrix3 = {
    r11 : float;
    r12 : float;
    r13 : float;
    r14 : float;
    r21 : float;
    r22 : float;
    r23 : float;
    r24 : float;
    r31 : float;
    r32 : float;
    r33 : float;
    r34 : float;
  }
  type dMatrix4 = {
    s11 : float;
    s12 : float;
    s13 : float;
    s14 : float;
    s21 : float;
    s22 : float;
    s23 : float;
    s24 : float;
    s31 : float;
    s32 : float;
    s33 : float;
    s34 : float;
    s41 : float;
    s42 : float;
    s43 : float;
    s44 : float;
  }
  type dMatrix6 = {
    t11 : float;
    t12 : float;
    t13 : float;
    t14 : float;
    t15 : float;
    t16 : float;
    t17 : float;
    t18 : float;
    t21 : float;
    t22 : float;
    t23 : float;
    t24 : float;
    t25 : float;
    t26 : float;
    t27 : float;
    t28 : float;
    t31 : float;
    t32 : float;
    t33 : float;
    t34 : float;
    t35 : float;
    t36 : float;
    t37 : float;
    t38 : float;
    t41 : float;
    t42 : float;
    t43 : float;
    t44 : float;
    t45 : float;
    t46 : float;
    t47 : float;
    t48 : float;
    t51 : float;
    t52 : float;
    t53 : float;
    t54 : float;
    t55 : float;
    t56 : float;
    t57 : float;
    t58 : float;
    t61 : float;
    t62 : float;
    t63 : float;
    t64 : float;
    t65 : float;
    t66 : float;
    t67 : float;
    t68 : float;
  }
  type dQuaternion = { q1 : float; q2 : float; q3 : float; q4 : float; }
  type ('a, 'b) dContactGeom = {
    cg_pos : Ode.LowLevel.dVector3;
    cg_normal : Ode.LowLevel.dVector3;
    cg_depth : float;
    cg_g1 : 'Ode.LowLevel.dGeomID;
    cg_g2 : 'Ode.LowLevel.dGeomID;
  }
  type ('a, 'b) dContact = {
    c_surface : Ode.LowLevel.dSurfaceParameters;
    c_geom : ('a, 'b) Ode.LowLevel.dContactGeom;
    c_fdir1 : Ode.LowLevel.dVector3;
  }
  and dSurfaceParameters = {
    sp_mode :
      [ `dContactApprox1
      | `dContactApprox1_1
      | `dContactApprox1_2
      | `dContactBounce
      | `dContactFDir1
      | `dContactMotion1
      | `dContactMotion2
      | `dContactMu2
      | `dContactSlip1
      | `dContactSlip2
      | `dContactSoftCFM
      | `dContactSoftERP ] list;
    sp_mu : float;
    sp_mu2 : float;
    sp_bounce : float;
    sp_bounce_vel : float;
    sp_soft_erp : float;
    sp_soft_cfm : float;
    sp_motion1 : float;
    sp_motion2 : float;
    sp_slip1 : float;
    sp_slip2 : float;
  }
  val surf_param_zero : Ode.LowLevel.dSurfaceParameters
  val get_surface :
    mu:float ->
    ?mu2:float ->
    ?bounce:float ->
    ?bounce_vel:float ->
    ?soft_erp:float ->
    ?soft_cfm:float ->
    ?motion1:float ->
    ?motion2:float ->
    ?slip1:float -> ?slip2:float -> unit -> Ode.LowLevel.dSurfaceParameters
  type surface_parameter =
      Mu2 of float
    | Bounce of float
    | BounceVel of float
    | SoftERP of float
    | SoftCFM of float
    | Motion1 of float
    | Motion2 of float
    | Slip1 of float
    | Slip2 of float
  val surface_param :
    mu:float ->
    Ode.LowLevel.surface_parameter list -> Ode.LowLevel.dSurfaceParameters
  type joint_type =
      JointTypeNone
    | JointTypeBall
    | JointTypeHinge
    | JointTypeSlider
    | JointTypeContact
    | JointTypeUniversal
    | JointTypeHinge2
    | JointTypeFixed
    | JointTypeNull
    | JointTypeAMotor
    | JointTypeLMotor
    | JointTypePlane2D
    | JointTypePR
  type dJointParam =
      DParamLoStop
    | DParamHiStop
    | DParamVel
    | DParamFMax
    | DParamFudgeFactor
    | DParamBounce
    | DParamCFM
    | DParamStopERP
    | DParamStopCFM
    | DParamSuspensionERP
    | DParamSuspensionCFM
    | DParamERP
    | DParamLoStop2
    | DParamHiStop2
    | DParamVel2
    | DParamFMax2
    | DParamFudgeFactor2
    | DParamBounce2
    | DParamCFM2
    | DParamStopERP2
    | DParamStopCFM2
    | DParamSuspensionERP2
    | DParamSuspensionCFM2
    | DParamERP2
    | DParamLoStop3
    | DParamHiStop3
    | DParamVel3
    | DParamFMax3
    | DParamFudgeFactor3
    | DParamBounce3
    | DParamCFM3
    | DParamStopERP3
    | DParamStopCFM3
    | DParamSuspensionERP3
    | DParamSuspensionCFM3
    | DParamERP3
    | DParamGroup
  external dGetInfinity : unit -> float = "ocamlode_dGetInfinity"
  val dInfinity : float
  external dInitODE : unit -> unit = "ocamlode_dInitODE"
  external dCloseODE : unit -> unit = "ocamlode_dCloseODE"
  type dInitODEFlags = DInitFlagManualThreadCleanup
  external dInitODE2 : initFlags:Ode.LowLevel.dInitODEFlags list -> unit
    = "ocamlode_dInitODE2"
  external dWorldCreate : unit -> Ode.LowLevel.dWorldID
    = "ocamlode_dWorldCreate"
  external dWorldDestroy : Ode.LowLevel.dWorldID -> unit
    = "ocamlode_dWorldDestroy"
  external dWorldSetGravity :
    Ode.LowLevel.dWorldID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dWorldSetGravity"
  external dWorldGetGravity : Ode.LowLevel.dWorldID -> Ode.LowLevel.dVector3
    = "ocamlode_dWorldGetGravity"
  external dWorldSetERP : Ode.LowLevel.dWorldID -> erp:float -> unit
    = "ocamlode_dWorldSetERP"
  external dWorldGetERP : Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetERP"
  external dWorldSetCFM : Ode.LowLevel.dWorldID -> cfm:float -> unit
    = "ocamlode_dWorldSetCFM"
  external dWorldGetCFM : Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetCFM"
  external dWorldStep : Ode.LowLevel.dWorldID -> float -> unit
    = "ocamlode_dWorldStep"
  external dWorldQuickStep : Ode.LowLevel.dWorldID -> float -> unit
    = "ocamlode_dWorldQuickStep"
  external dWorldStepFast1 :
    Ode.LowLevel.dWorldID -> stepsize:float -> maxiterations:int -> unit
    = "ocamlode_dWorldStepFast1"
  external dWorldSetAutoEnableDepthSF1 : Ode.LowLevel.dWorldID -> int -> unit
    = "ocamlode_dWorldSetAutoEnableDepthSF1"
  external dWorldGetAutoEnableDepthSF1 : Ode.LowLevel.dWorldID -> int
    = "ocamlode_dWorldGetAutoEnableDepthSF1"
  external dWorldSetQuickStepNumIterations :
    Ode.LowLevel.dWorldID -> num:int -> unit
    = "ocamlode_dWorldSetQuickStepNumIterations"
  external dWorldGetQuickStepNumIterations : Ode.LowLevel.dWorldID -> int
    = "ocamlode_dWorldGetQuickStepNumIterations"
  external dWorldSetContactSurfaceLayer :
    Ode.LowLevel.dWorldID -> depth:float -> unit
    = "ocamlode_dWorldSetContactSurfaceLayer"
  external dWorldGetContactSurfaceLayer : Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetContactSurfaceLayer"
  external dWorldSetAutoDisableLinearThreshold :
    Ode.LowLevel.dWorldID -> linear_threshold:float -> unit
    = "ocamlode_dWorldSetAutoDisableLinearThreshold"
  external dWorldGetAutoDisableLinearThreshold :
    Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetAutoDisableLinearThreshold"
  external dWorldSetAutoDisableAngularThreshold :
    Ode.LowLevel.dWorldID -> angular_threshold:float -> unit
    = "ocamlode_dWorldSetAutoDisableAngularThreshold"
  external dWorldGetAutoDisableAngularThreshold :
    Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetAutoDisableAngularThreshold"
  external dWorldSetAutoDisableAverageSamplesCount :
    Ode.LowLevel.dWorldID -> average_samples_count:int -> unit
    = "ocamlode_dWorldSetAutoDisableAverageSamplesCount"
  external dWorldGetAutoDisableAverageSamplesCount :
    Ode.LowLevel.dWorldID -> int
    = "ocamlode_dWorldGetAutoDisableAverageSamplesCount"
  external dWorldSetAutoDisableSteps :
    Ode.LowLevel.dWorldID -> steps:int -> unit
    = "ocamlode_dWorldSetAutoDisableSteps"
  external dWorldGetAutoDisableSteps : Ode.LowLevel.dWorldID -> int
    = "ocamlode_dWorldGetAutoDisableSteps"
  external dWorldSetAutoDisableTime :
    Ode.LowLevel.dWorldID -> time:float -> unit
    = "ocamlode_dWorldSetAutoDisableTime"
  external dWorldGetAutoDisableTime : Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetAutoDisableTime"
  external dWorldSetAutoDisableFlag :
    Ode.LowLevel.dWorldID -> do_auto_disable:bool -> unit
    = "ocamlode_dWorldSetAutoDisableFlag"
  external dWorldGetAutoDisableFlag : Ode.LowLevel.dWorldID -> bool
    = "ocamlode_dWorldGetAutoDisableFlag"
  external dWorldSetQuickStepW :
    Ode.LowLevel.dWorldID -> over_relaxation:float -> unit
    = "ocamlode_dWorldSetQuickStepW"
  external dWorldGetQuickStepW : Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetQuickStepW"
  external dWorldSetContactMaxCorrectingVel :
    Ode.LowLevel.dWorldID -> vel:float -> unit
    = "ocamlode_dWorldSetContactMaxCorrectingVel"
  external dWorldGetContactMaxCorrectingVel : Ode.LowLevel.dWorldID -> float
    = "ocamlode_dWorldGetContactMaxCorrectingVel"
  external dBodyCreate : Ode.LowLevel.dWorldID -> Ode.LowLevel.dBodyID
    = "ocamlode_dBodyCreate"
  external dBodyDestroy : Ode.LowLevel.dBodyID -> unit
    = "ocamlode_dBodyDestroy"
  external dBodyGetWorld : Ode.LowLevel.dBodyID -> Ode.LowLevel.dWorldID
    = "ocamlode_dBodyGetWorld"
  external dBodySetPosition :
    Ode.LowLevel.dBodyID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dBodySetPosition"
  external dBodySetRotation :
    Ode.LowLevel.dBodyID -> Ode.LowLevel.dMatrix3 -> unit
    = "ocamlode_dBodySetRotation"
  external dBodySetQuaternion :
    Ode.LowLevel.dBodyID -> Ode.LowLevel.dQuaternion -> unit
    = "ocamlode_dBodySetQuaternion"
  external dBodySetLinearVel :
    Ode.LowLevel.dBodyID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dBodySetLinearVel"
  external dBodySetAngularVel :
    Ode.LowLevel.dBodyID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dBodySetAngularVel"
  external dBodyGetPosition : Ode.LowLevel.dBodyID -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetPosition"
  external dBodyGetRotation : Ode.LowLevel.dBodyID -> Ode.LowLevel.dMatrix3
    = "ocamlode_dBodyGetRotation"
  external dBodyGetQuaternion :
    Ode.LowLevel.dBodyID -> Ode.LowLevel.dQuaternion
    = "ocamlode_dBodyGetQuaternion"
  external dBodyGetLinearVel : Ode.LowLevel.dBodyID -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetLinearVel"
  external dBodyGetAngularVel : Ode.LowLevel.dBodyID -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetAngularVel"
  external dBodySetMass : Ode.LowLevel.dBodyID -> Ode.LowLevel.dMass -> unit
    = "ocamlode_dBodySetMass"
  external dBodyGetMass : Ode.LowLevel.dBodyID -> Ode.LowLevel.dMass
    = "ocamlode_dBodyGetMass"
  external dBodyAddForce :
    Ode.LowLevel.dBodyID -> fx:float -> fy:float -> fz:float -> unit
    = "ocamlode_dBodyAddForce"
  external dBodyAddTorque :
    Ode.LowLevel.dBodyID -> fx:float -> fy:float -> fz:float -> unit
    = "ocamlode_dBodyAddTorque"
  external dBodyAddRelForce :
    Ode.LowLevel.dBodyID -> fx:float -> fy:float -> fz:float -> unit
    = "ocamlode_dBodyAddRelForce"
  external dBodyAddRelTorque :
    Ode.LowLevel.dBodyID -> fx:float -> fy:float -> fz:float -> unit
    = "ocamlode_dBodyAddRelTorque"
  external dBodyAddForceAtPos :
    Ode.LowLevel.dBodyID ->
    fx:float ->
    fy:float -> fz:float -> px:float -> py:float -> pz:float -> unit
    = "ocamlode_dBodyAddForceAtPos_bc" "ocamlode_dBodyAddForceAtPos"
  external dBodyAddForceAtRelPos :
    Ode.LowLevel.dBodyID ->
    fx:float ->
    fy:float -> fz:float -> px:float -> py:float -> pz:float -> unit
    = "ocamlode_dBodyAddForceAtRelPos_bc" "ocamlode_dBodyAddForceAtRelPos"
  external dBodyAddRelForceAtPos :
    Ode.LowLevel.dBodyID ->
    fx:float ->
    fy:float -> fz:float -> px:float -> py:float -> pz:float -> unit
    = "ocamlode_dBodyAddRelForceAtPos_bc" "ocamlode_dBodyAddRelForceAtPos"
  external dBodyAddRelForceAtRelPos :
    Ode.LowLevel.dBodyID ->
    fx:float ->
    fy:float -> fz:float -> px:float -> py:float -> pz:float -> unit
    = "ocamlode_dBodyAddRelForceAtRelPos_bc"
    "ocamlode_dBodyAddRelForceAtRelPos"
  external dBodySetForce :
    Ode.LowLevel.dBodyID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dBodySetForce"
  external dBodySetTorque :
    Ode.LowLevel.dBodyID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dBodySetTorque"
  external dBodyGetForce : Ode.LowLevel.dBodyID -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetForce"
  external dBodyGetTorque : Ode.LowLevel.dBodyID -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetTorque"
  external dBodyGetRelPointPos :
    Ode.LowLevel.dBodyID ->
    px:float -> py:float -> pz:float -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetRelPointPos"
  external dBodyGetPosRelPoint :
    Ode.LowLevel.dBodyID ->
    px:float -> py:float -> pz:float -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetPosRelPoint"
  external dBodyGetRelPointVel :
    Ode.LowLevel.dBodyID ->
    px:float -> py:float -> pz:float -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetRelPointVel"
  external dBodyGetPointVel :
    Ode.LowLevel.dBodyID ->
    px:float -> py:float -> pz:float -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetPointVel"
  external dBodyVectorToWorld :
    Ode.LowLevel.dBodyID ->
    px:float -> py:float -> pz:float -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyVectorToWorld"
  external dBodyVectorFromWorld :
    Ode.LowLevel.dBodyID ->
    px:float -> py:float -> pz:float -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyVectorFromWorld"
  external dBodyEnable : Ode.LowLevel.dBodyID -> unit
    = "ocamlode_dBodyEnable"
  external dBodyDisable : Ode.LowLevel.dBodyID -> unit
    = "ocamlode_dBodyDisable"
  external dBodyIsEnabled : Ode.LowLevel.dBodyID -> bool
    = "ocamlode_dBodyIsEnabled"
  external dBodySetAutoDisableFlag : Ode.LowLevel.dBodyID -> bool -> unit
    = "ocamlode_dBodySetAutoDisableFlag"
  external dBodyGetAutoDisableFlag : Ode.LowLevel.dBodyID -> bool
    = "ocamlode_dBodyGetAutoDisableFlag"
  external dBodySetAutoDisableSteps :
    Ode.LowLevel.dBodyID -> steps:int -> unit
    = "ocamlode_dBodySetAutoDisableSteps"
  external dBodyGetAutoDisableSteps : Ode.LowLevel.dBodyID -> int
    = "ocamlode_dBodyGetAutoDisableSteps"
  external dBodySetAutoDisableTime :
    Ode.LowLevel.dBodyID -> time:float -> unit
    = "ocamlode_dBodySetAutoDisableTime"
  external dBodyGetAutoDisableTime : Ode.LowLevel.dBodyID -> float
    = "ocamlode_dBodyGetAutoDisableTime"
  external dAreConnected :
    a:Ode.LowLevel.dBodyID -> b:Ode.LowLevel.dBodyID -> bool
    = "ocamlode_dAreConnected"
  external dAreConnectedExcluding :
    a:Ode.LowLevel.dBodyID ->
    b:Ode.LowLevel.dBodyID -> Ode.LowLevel.joint_type -> bool
    = "ocamlode_dAreConnectedExcluding"
  external dBodySetGravityMode : Ode.LowLevel.dBodyID -> mode:bool -> unit
    = "ocamlode_dBodySetGravityMode"
  external dBodyGetGravityMode : Ode.LowLevel.dBodyID -> bool
    = "ocamlode_dBodyGetGravityMode"
  external dBodySetFiniteRotationMode :
    Ode.LowLevel.dBodyID -> mode:bool -> unit
    = "ocamlode_dBodySetFiniteRotationMode"
  external dBodyGetFiniteRotationMode : Ode.LowLevel.dBodyID -> bool
    = "ocamlode_dBodyGetFiniteRotationMode"
  external dBodySetFiniteRotationAxis :
    Ode.LowLevel.dBodyID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dBodySetFiniteRotationAxis"
  external dBodyGetFiniteRotationAxis :
    Ode.LowLevel.dBodyID -> Ode.LowLevel.dVector3
    = "ocamlode_dBodyGetFiniteRotationAxis"
  external dBodySetAutoDisableLinearThreshold :
    Ode.LowLevel.dBodyID -> linear_average_threshold:float -> unit
    = "ocamlode_dBodySetAutoDisableLinearThreshold"
  external dBodyGetAutoDisableLinearThresholda :
    Ode.LowLevel.dBodyID -> float
    = "ocamlode_dBodyGetAutoDisableLinearThreshold"
  external dBodySetAutoDisableAngularThreshold :
    Ode.LowLevel.dBodyID -> angular_average_threshold:float -> unit
    = "ocamlode_dBodySetAutoDisableAngularThreshold"
  external dBodyGetAutoDisableAngularThreshold :
    Ode.LowLevel.dBodyID -> float
    = "ocamlode_dBodyGetAutoDisableAngularThreshold"
  external dBodySetAutoDisableAverageSamplesCount :
    Ode.LowLevel.dBodyID -> average_samples_count:int -> unit
    = "ocamlode_dBodySetAutoDisableAverageSamplesCount"
  external dBodyGetAutoDisableAverageSamplesCount :
    Ode.LowLevel.dBodyID -> int
    = "ocamlode_dBodyGetAutoDisableAverageSamplesCount"
  external dBodySetData : Ode.LowLevel.dBodyID -> int -> unit
    = "ocamlode_dBodySetData"
  external dBodyGetData : Ode.LowLevel.dBodyID -> int
    = "ocamlode_dBodyGetData"
  external dJointCreateBall :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateBall"
  external dJointCreateHinge :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateHinge"
  external dJointCreateSlider :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateSlider"
  external dJointCreateContact :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option ->
    ('a, 'b) Ode.LowLevel.dContact -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateContact"
  external dJointCreateUniversal :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateUniversal"
  external dJointCreateHinge2 :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateHinge2"
  external dJointCreateFixed :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateFixed"
  external dJointCreateAMotor :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateAMotor"
  external dJointCreateLMotor :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreateLMotor"
  external dJointCreatePlane2D :
    Ode.LowLevel.dWorldID ->
    Ode.LowLevel.dJointGroupID option -> Ode.LowLevel.dJointID
    = "ocamlode_dJointCreatePlane2D"
  external dJointDestroy : Ode.LowLevel.dJointID -> unit
    = "ocamlode_dJointDestroy"
  external dJointGroupCreate : unit -> Ode.LowLevel.dJointGroupID
    = "ocamlode_dJointGroupCreate"
  external dJointGroupDestroy : Ode.LowLevel.dJointGroupID -> unit
    = "ocamlode_dJointGroupDestroy"
  external dJointGroupEmpty : Ode.LowLevel.dJointGroupID -> unit
    = "ocamlode_dJointGroupEmpty"
  external dJointAttach :
    Ode.LowLevel.dJointID ->
    Ode.LowLevel.dBodyID option -> Ode.LowLevel.dBodyID option -> unit
    = "ocamlode_dJointAttach"
  external dJointSetSliderAxis :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetSliderAxis"
  external dJointGetSliderAxis :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetSliderAxis"
  external dJointGetSliderPosition : Ode.LowLevel.dJointID -> float
    = "ocamlode_dJointGetSliderPosition"
  external dJointGetSliderPositionRate : Ode.LowLevel.dJointID -> float
    = "ocamlode_dJointGetSliderPositionRate"
  external dJointSetHingeParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetHingeParam"
  external dJointSetSliderParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetSliderParam"
  external dJointSetHinge2Param :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetHinge2Param"
  external dJointSetUniversalParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetUniversalParam"
  external dJointSetAMotorParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetAMotorParam"
  external dJointSetLMotorParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetLMotorParam"
  external dJointGetHingeParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float
    = "ocamlode_dJointGetHingeParam"
  external dJointGetSliderParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float
    = "ocamlode_dJointGetSliderParam"
  external dJointGetHinge2Param :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float
    = "ocamlode_dJointGetHinge2Param"
  external dJointGetUniversalParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float
    = "ocamlode_dJointGetUniversalParam"
  external dJointGetAMotorParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float
    = "ocamlode_dJointGetAMotorParam"
  external dJointGetLMotorParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float
    = "ocamlode_dJointGetLMotorParam"
  external dJointSetBallAnchor :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetBallAnchor"
  external dJointSetBallAnchor2 :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetBallAnchor2"
  external dJointSetHingeAnchor :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetHingeAnchor"
  external dJointSetHingeAnchorDelta :
    Ode.LowLevel.dJointID ->
    x:float -> y:float -> z:float -> ax:float -> ay:float -> az:float -> unit
    = "ocamlode_dJointSetHingeAnchorDelta_bytecode"
    "ocamlode_dJointSetHingeAnchorDelta"
  external dJointSetHingeAxis :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetHingeAxis"
  external dJointAddHingeTorque :
    Ode.LowLevel.dJointID -> torque:float -> unit
    = "ocamlode_dJointAddHingeTorque"
  external dJointSetSliderAxisDelta :
    Ode.LowLevel.dJointID ->
    x:float -> y:float -> z:float -> ax:float -> ay:float -> az:float -> unit
    = "ocamlode_dJointSetSliderAxisDelta_bytecode"
    "ocamlode_dJointSetSliderAxisDelta"
  external dJointAddSliderForce :
    Ode.LowLevel.dJointID -> force:float -> unit
    = "ocamlode_dJointAddSliderForce"
  external dJointSetHinge2Anchor :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetHinge2Anchor"
  external dJointSetHinge2Axis1 :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetHinge2Axis1"
  external dJointSetHinge2Axis2 :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetHinge2Axis2"
  external dJointAddHinge2Torques :
    Ode.LowLevel.dJointID -> torque1:float -> torque2:float -> unit
    = "ocamlode_dJointAddHinge2Torques"
  external dJointSetUniversalAnchor :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetUniversalAnchor"
  external dJointSetUniversalAxis1 :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetUniversalAxis1"
  external dJointSetUniversalAxis2 :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetUniversalAxis2"
  external dJointAddUniversalTorques :
    Ode.LowLevel.dJointID -> torque1:float -> torque2:float -> unit
    = "ocamlode_dJointAddUniversalTorques"
  external dJointSetPRAnchor :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetPRAnchor"
  external dJointSetPRAxis1 :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetPRAxis1"
  external dJointSetPRAxis2 :
    Ode.LowLevel.dJointID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetPRAxis2"
  external dJointSetPRParam :
    Ode.LowLevel.dJointID -> parameter:int -> value:float -> unit
    = "ocamlode_dJointSetPRParam"
  external dJointAddPRTorque : Ode.LowLevel.dJointID -> torque:float -> unit
    = "ocamlode_dJointAddPRTorque"
  external dJointSetFixed : Ode.LowLevel.dJointID -> unit
    = "ocamlode_dJointSetFixed"
  external dJointSetAMotorNumAxes : Ode.LowLevel.dJointID -> num:int -> unit
    = "ocamlode_dJointSetAMotorNumAxes"
  external dJointSetAMotorAxis :
    Ode.LowLevel.dJointID ->
    anum:int -> rel:int -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetAMotorAxis_bc" "ocamlode_dJointSetAMotorAxis"
  external dJointSetAMotorAngle :
    Ode.LowLevel.dJointID -> anum:int -> angle:float -> unit
    = "ocamlode_dJointSetAMotorAngle"
  external dJointSetAMotorMode : Ode.LowLevel.dJointID -> mode:int -> unit
    = "ocamlode_dJointSetAMotorMode"
  external dJointAddAMotorTorques :
    Ode.LowLevel.dJointID ->
    torque1:float -> torque2:float -> torque3:float -> unit
    = "ocamlode_dJointAddAMotorTorques"
  external dJointSetLMotorNumAxes : Ode.LowLevel.dJointID -> num:int -> unit
    = "ocamlode_dJointSetLMotorNumAxes"
  external dJointSetLMotorAxis :
    Ode.LowLevel.dJointID ->
    anum:int -> rel:int -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dJointSetLMotorAxis_bc" "ocamlode_dJointSetLMotorAxis"
  external dJointSetPlane2DXParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetPlane2DXParam"
  external dJointSetPlane2DYParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetPlane2DYParam"
  external dJointSetPlane2DAngleParam :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointParam -> float -> unit
    = "ocamlode_dJointSetPlane2DAngleParam"
  external dJointGetBallAnchor :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetBallAnchor"
  external dJointGetBallAnchor2 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetBallAnchor2"
  external dJointGetHingeAnchor :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetHingeAnchor"
  external dJointGetHingeAnchor2 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetHingeAnchor2"
  external dJointGetHingeAxis :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetHingeAxis"
  external dJointGetHingeAngle : Ode.LowLevel.dJointID -> float
    = "ocamlode_dJointGetHingeAngle"
  external dJointGetHingeAngleRate : Ode.LowLevel.dJointID -> float
    = "ocamlode_dJointGetHingeAngleRate"
  external dJointGetHinge2Anchor :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetHinge2Anchor"
  external dJointGetHinge2Anchor2 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetHinge2Anchor2"
  external dJointGetHinge2Axis1 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetHinge2Axis1"
  external dJointGetHinge2Axis2 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetHinge2Axis2"
  external dJointGetHinge2Angle1 : Ode.LowLevel.dJointID -> float
    = "ocamlode_dJointGetHinge2Angle1"
  external dJointGetHinge2Angle1Rate : Ode.LowLevel.dJointID -> float
    = "ocamlode_dJointGetHinge2Angle1Rate"
  external dJointGetHinge2Angle2Rate : Ode.LowLevel.dJointID -> float
    = "ocamlode_dJointGetHinge2Angle2Rate"
  external dJointGetUniversalAnchor :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetUniversalAnchor"
  external dJointGetUniversalAnchor2 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetUniversalAnchor2"
  external dJointGetUniversalAxis1 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetUniversalAxis1"
  external dJointGetUniversalAxis2 :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dVector3
    = "ocamlode_dJointGetUniversalAxis2"
  external dBodyGetNumJoints : Ode.LowLevel.dBodyID -> int
    = "ocamlode_dBodyGetNumJoints"
  external dBodyGetJoint :
    Ode.LowLevel.dBodyID -> index:int -> Ode.LowLevel.dJointID
    = "ocamlode_dBodyGetJoint"
  external dConnectingJoint :
    Ode.LowLevel.dBodyID -> Ode.LowLevel.dBodyID -> Ode.LowLevel.dJointID
    = "ocamlode_dConnectingJoint"
  external dConnectingJointList :
    Ode.LowLevel.dBodyID ->
    Ode.LowLevel.dBodyID -> Ode.LowLevel.dJointID array
    = "ocamlode_dConnectingJointList"
  external dJointSetData : Ode.LowLevel.dJointID -> data:int -> unit
    = "ocamlode_dJointSetData"
  external dJointGetData : Ode.LowLevel.dJointID -> int
    = "ocamlode_dJointGetData"
  external dJointGetType : Ode.LowLevel.dJointID -> Ode.LowLevel.joint_type
    = "ocamlode_dJointGetType"
  external dJointGetBody :
    Ode.LowLevel.dJointID -> index:int -> Ode.LowLevel.dBodyID
    = "ocamlode_dJointGetBody"
  type dJointFeedback = {
    f1 : Ode.LowLevel.dVector3;
    t1 : Ode.LowLevel.dVector3;
    f2 : Ode.LowLevel.dVector3;
    t2 : Ode.LowLevel.dVector3;
  }
  type dJointFeedbackBuffer
  external dJointSetFeedback :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointFeedbackBuffer
    = "ocamlode_dJointSetFeedback"
  external dJointFeedbackBufferDestroy :
    Ode.LowLevel.dJointFeedbackBuffer -> unit
    = "ocamlode_dJointFeedbackBufferDestroy"
  external dJointGetFeedback :
    Ode.LowLevel.dJointID -> Ode.LowLevel.dJointFeedback
    = "ocamlode_dJointGetFeedback"
  external dJointFeedback_of_buffer :
    Ode.LowLevel.dJointFeedbackBuffer -> Ode.LowLevel.dJointFeedback
    = "ocamlode_dJointFeedback_of_buffer"
  external dSimpleSpaceCreate :
    Ode.LowLevel.dSpaceID option -> Ode.LowLevel.dSpaceID
    = "ocamlode_dSimpleSpaceCreate"
  external dHashSpaceCreate :
    Ode.LowLevel.dSpaceID option -> Ode.LowLevel.dSpaceID
    = "ocamlode_dHashSpaceCreate"
  external dQuadTreeSpaceCreate :
    Ode.LowLevel.dSpaceID option ->
    center:Ode.LowLevel.dVector3 ->
    extents:Ode.LowLevel.dVector3 -> depth:int -> Ode.LowLevel.dSpaceID
    = "ocamlode_dQuadTreeSpaceCreate"
  external dSpaceDestroy : Ode.LowLevel.dSpaceID -> unit
    = "ocamlode_dSpaceDestroy"
  external dHashSpaceSetLevels :
    Ode.LowLevel.dSpaceID -> minlevel:int -> maxlevel:int -> unit
    = "ocamlode_dHashSpaceSetLevels"
  external dHashSpaceGetLevels : Ode.LowLevel.dSpaceID -> int * int
    = "ocamlode_dHashSpaceGetLevels"
  external dSpaceAdd :
    Ode.LowLevel.dSpaceID -> 'Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dSpaceAdd"
  external dSpaceRemove :
    Ode.LowLevel.dSpaceID -> 'Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dSpaceRemove"
  external dSpaceCollide :
    Ode.LowLevel.dSpaceID ->
    ('Ode.LowLevel.dGeomID -> 'Ode.LowLevel.dGeomID -> unit) -> unit
    = "ocamlode_dSpaceCollide"
  external dSpaceCollide2 :
    'Ode.LowLevel.dGeomID ->
    'Ode.LowLevel.dGeomID ->
    ('Ode.LowLevel.dGeomID -> 'Ode.LowLevel.dGeomID -> unit) -> unit
    = "ocamlode_dSpaceCollide2"
  external dSpaceSetCleanup : Ode.LowLevel.dSpaceID -> mode:bool -> unit
    = "ocamlode_dSpaceSetCleanup"
  external dSpaceGetCleanup : Ode.LowLevel.dSpaceID -> bool
    = "ocamlode_dSpaceGetCleanup"
  external dSpaceClean : Ode.LowLevel.dSpaceID -> unit
    = "ocamlode_dSpaceClean"
  external dSpaceQuery :
    Ode.LowLevel.dSpaceID -> 'Ode.LowLevel.dGeomID -> bool
    = "ocamlode_dSpaceQuery"
  external dSpaceGetNumGeoms : Ode.LowLevel.dSpaceID -> unit
    = "ocamlode_dSpaceGetNumGeoms"
  external dSpaceGetGeom :
    Ode.LowLevel.dSpaceID -> i:int -> 'Ode.LowLevel.dGeomID
    = "ocamlode_dSpaceGetGeom"
  external dSpaceGetGeomsArray :
    Ode.LowLevel.dSpaceID -> 'Ode.LowLevel.dGeomID array
    = "ocamlode_dSpaceGetGeomsArray"
  external dCollide :
    'Ode.LowLevel.dGeomID ->
    'Ode.LowLevel.dGeomID ->
    max:int -> ('a, 'b) Ode.LowLevel.dContactGeom array = "ocamlode_dCollide"
  external dGeomDestroy : 'Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dGeomDestroy"
  external dGeomSetBody :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dBodyID option -> unit
    = "ocamlode_dGeomSetBody"
  external dGeomGetBody :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dBodyID option
    = "ocamlode_dGeomGetBody"
  external dGeomSetPosition :
    'Ode.LowLevel.dGeomID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dGeomSetPosition"
  external dGeomSetRotation :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dMatrix3 -> unit
    = "ocamlode_dGeomSetRotation"
  external dGeomSetQuaternion :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dQuaternion -> unit
    = "ocamlode_dGeomSetQuaternion"
  external dGeomGetPosition :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dVector3
    = "ocamlode_dGeomGetPosition"
  external dGeomGetRotation :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dMatrix3
    = "ocamlode_dGeomGetRotation"
  external dGeomGetQuaternion :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dQuaternion
    = "ocamlode_dGeomGetQuaternion"
  external dGeomGetAABB : 'Ode.LowLevel.dGeomID -> float array
    = "ocamlode_dGeomGetAABB"
  external dInfiniteAABB : 'Ode.LowLevel.dGeomID -> float array
    = "ocamlode_dInfiniteAABB"
  type sphere_geom
  type box_geom
  type plane_geom
  type heightfield_geom
  type trimesh_geom
  type convex_geom
  type capsule_geom
  type cylinder_geom
  type ray_geom
  type geomTransform_geom
  type geom_class =
      SphereClass
    | BoxClass
    | CapsuleClass
    | CylinderClass
    | PlaneClass
    | RayClass
    | ConvexClass
    | GeomTransformClass
    | TriMeshClass
    | HeightfieldClass
    | FirstSpaceSimpleSpaceClass
    | HashSpaceClass
    | LastSpaceQuadTreeSpaceClass
    | FirstUserClass
    | LastUserClass
  external dGeomGetClass : 'Ode.LowLevel.dGeomID -> Ode.LowLevel.geom_class
    = "ocamlode_dGeomGetClass"
  type geom_type =
      Sphere_geom of Ode.LowLevel.sphere_geom Ode.LowLevel.dGeomID
    | Box_geom of Ode.LowLevel.box_geom Ode.LowLevel.dGeomID
    | Capsule_geom of Ode.LowLevel.capsule_geom Ode.LowLevel.dGeomID
    | Cylinder_geom of Ode.LowLevel.cylinder_geom Ode.LowLevel.dGeomID
    | Plane_geom of Ode.LowLevel.plane_geom Ode.LowLevel.dGeomID
    | Ray_geom of Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID
    | Convex_geom of Ode.LowLevel.convex_geom Ode.LowLevel.dGeomID
    | GeomTransform_geom of
        Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID
    | TriMesh_geom of Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID
    | Heightfield_geom of Ode.LowLevel.heightfield_geom Ode.LowLevel.dGeomID
    | Geom_is_space
    | User_class
  val geom_kind : 'Ode.LowLevel.dGeomID -> Ode.LowLevel.geom_type
  external dCreateSphere :
    Ode.LowLevel.dSpaceID option ->
    radius:float -> Ode.LowLevel.sphere_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateSphere"
  external dGeomSphereGetRadius :
    Ode.LowLevel.sphere_geom Ode.LowLevel.dGeomID -> float
    = "ocamlode_dGeomSphereGetRadius"
  external dGeomSphereSetRadius :
    Ode.LowLevel.sphere_geom Ode.LowLevel.dGeomID -> radius:float -> unit
    = "ocamlode_dGeomSphereSetRadius"
  external dGeomSpherePointDepth :
    Ode.LowLevel.sphere_geom Ode.LowLevel.dGeomID ->
    x:float -> y:float -> z:float -> float = "ocamlode_dGeomSpherePointDepth"
  external dCreateBox :
    Ode.LowLevel.dSpaceID option ->
    lx:float ->
    ly:float -> lz:float -> Ode.LowLevel.box_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateBox"
  external dGeomBoxGetLengths :
    Ode.LowLevel.box_geom Ode.LowLevel.dGeomID -> Ode.LowLevel.dVector3
    = "ocamlode_dGeomBoxGetLengths"
  external dGeomBoxSetLengths :
    Ode.LowLevel.box_geom Ode.LowLevel.dGeomID ->
    lx:float -> ly:float -> lz:float -> unit = "ocamlode_dGeomBoxSetLengths"
  external dGeomBoxPointDepth :
    Ode.LowLevel.box_geom Ode.LowLevel.dGeomID ->
    x:float -> y:float -> z:float -> float = "ocamlode_dGeomBoxPointDepth"
  external dCreatePlane :
    Ode.LowLevel.dSpaceID option ->
    a:float ->
    b:float ->
    c:float -> d:float -> Ode.LowLevel.plane_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreatePlane"
  external dGeomPlaneGetParams :
    Ode.LowLevel.plane_geom Ode.LowLevel.dGeomID -> Ode.LowLevel.dVector4
    = "ocamlode_dGeomPlaneGetParams"
  external dGeomPlaneSetParams :
    Ode.LowLevel.plane_geom Ode.LowLevel.dGeomID ->
    a:float -> b:float -> c:float -> d:float -> unit
    = "ocamlode_dGeomPlaneSetParams"
  external dGeomPlanePointDepth :
    Ode.LowLevel.plane_geom Ode.LowLevel.dGeomID ->
    x:float -> y:float -> z:float -> unit = "ocamlode_dGeomPlanePointDepth"
  external dCreateCapsule :
    Ode.LowLevel.dSpaceID option ->
    radius:float ->
    length:float -> Ode.LowLevel.capsule_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateCapsule"
  external dGeomCapsuleGetParams :
    Ode.LowLevel.capsule_geom Ode.LowLevel.dGeomID -> float * float
    = "ocamlode_dGeomCapsuleGetParams"
  external dGeomCapsuleSetParams :
    Ode.LowLevel.capsule_geom Ode.LowLevel.dGeomID ->
    radius:float -> length:float -> unit = "ocamlode_dGeomCapsuleSetParams"
  external dGeomCapsulePointDepth :
    Ode.LowLevel.capsule_geom Ode.LowLevel.dGeomID ->
    x:float -> y:float -> z:float -> unit = "ocamlode_dGeomCapsulePointDepth"
  external dCreateCylinder :
    Ode.LowLevel.dSpaceID option ->
    radius:float ->
    length:float -> Ode.LowLevel.cylinder_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateCylinder"
  external dGeomCylinderGetParams :
    Ode.LowLevel.cylinder_geom Ode.LowLevel.dGeomID -> float * float
    = "ocamlode_dGeomCylinderGetParams"
  external dGeomCylinderSetParams :
    Ode.LowLevel.cylinder_geom Ode.LowLevel.dGeomID ->
    radius:float -> length:float -> unit = "ocamlode_dGeomCylinderSetParams"
  external dCreateRay :
    Ode.LowLevel.dSpaceID option ->
    length:float -> Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateRay"
  external dGeomRaySetLength :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID -> length:float -> unit
    = "ocamlode_dGeomRaySetLength"
  external dGeomRayGetLength :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID -> float
    = "ocamlode_dGeomRayGetLength"
  external dGeomRaySet :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID ->
    px:float ->
    py:float -> pz:float -> dx:float -> dy:float -> dz:float -> unit
    = "ocamlode_dGeomRaySet_bytecode" "ocamlode_dGeomRaySet_native"
  external dGeomRayGet :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID ->
    Ode.LowLevel.dVector3 * Ode.LowLevel.dVector3 = "ocamlode_dGeomRayGet"
  external dGeomRaySetParams :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID ->
    first_contact:bool -> backface_cull:bool -> unit
    = "ocamlode_dGeomRaySetParams"
  external dGeomRayGetParams :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID -> bool * bool
    = "ocamlode_dGeomRayGetParams"
  external dGeomRaySetClosestHit :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID -> closest_hit:bool -> unit
    = "ocamlode_dGeomRaySetClosestHit"
  external dGeomRayGetClosestHit :
    Ode.LowLevel.ray_geom Ode.LowLevel.dGeomID -> bool
    = "ocamlode_dGeomRayGetClosestHit"
  type dTriMeshDataID
  external dGeomTriMeshDataCreate : unit -> Ode.LowLevel.dTriMeshDataID
    = "ocamlode_dGeomTriMeshDataCreate"
  external dGeomTriMeshDataDestroy : Ode.LowLevel.dTriMeshDataID -> unit
    = "ocamlode_dGeomTriMeshDataDestroy"
  external dGeomTriMeshDataPreprocess : Ode.LowLevel.dTriMeshDataID -> unit
    = "ocamlode_dGeomTriMeshDataPreprocess"
  external dGeomTriMeshSetData :
    Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID ->
    data:Ode.LowLevel.dTriMeshDataID -> unit = "ocamlode_dGeomTriMeshSetData"
  external dGeomTriMeshGetData :
    Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID ->
    Ode.LowLevel.dTriMeshDataID = "ocamlode_dGeomTriMeshGetData"
  external dGeomTriMeshGetTriMeshDataID :
    Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID ->
    Ode.LowLevel.dTriMeshDataID = "ocamlode_dGeomTriMeshGetTriMeshDataID"
  external dGeomTriMeshDataUpdate : Ode.LowLevel.dTriMeshDataID -> unit
    = "ocamlode_dGeomTriMeshDataUpdate"
  external dGeomTriMeshDataBuild :
    Ode.LowLevel.dTriMeshDataID ->
    vertices:float array -> indices:int array -> unit
    = "ocamlode_dGeomTriMeshDataBuildDouble"
  external dCreateTriMesh :
    Ode.LowLevel.dSpaceID option ->
    Ode.LowLevel.dTriMeshDataID ->
    ?tri_cb:'->
    ?arr_cb:'->
    ?ray_cb:'-> unit -> Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateTriMesh_bytecode" "ocamlode_dCreateTriMesh_native"
  external dGeomTriMeshEnableTC :
    Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID ->
    Ode.LowLevel.geom_class -> bool -> unit = "ocamlode_dGeomTriMeshEnableTC"
  external dGeomTriMeshIsTCEnabled :
    Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID ->
    Ode.LowLevel.geom_class -> bool = "ocamlode_dGeomTriMeshIsTCEnabled"
  external dGeomTriMeshClearTCCache :
    Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dGeomTriMeshClearTCCache"
  external dCreateGeomTransform :
    Ode.LowLevel.dSpaceID option ->
    Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateGeomTransform"
  external dGeomTransformSetGeom :
    Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID ->
    'Ode.LowLevel.dGeomID option -> unit = "ocamlode_dGeomTransformSetGeom"
  external dGeomTransformGetGeom :
    Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID ->
    'Ode.LowLevel.dGeomID option = "ocamlode_dGeomTransformGetGeom"
  external dGeomTransformSetCleanup :
    Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID ->
    cleanup:bool -> unit = "ocamlode_dGeomTransformSetCleanup"
  external dGeomTransformGetCleanup :
    Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID -> bool
    = "ocamlode_dGeomTransformGetCleanup"
  external dGeomTransformSetInfo :
    Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID ->
    cleanup:bool -> unit = "ocamlode_dGeomTransformSetInfo"
  external dGeomTransformGetInfo :
    Ode.LowLevel.geomTransform_geom Ode.LowLevel.dGeomID -> bool
    = "ocamlode_dGeomTransformGetInfo"
  type dConvexDataID
  external dConvexDataBuild :
    planes:float array ->
    points:float array -> polygones:int array -> Ode.LowLevel.dConvexDataID
    = "ocamlode_get_dConvexDataID"
  external dCreateConvex :
    Ode.LowLevel.dSpaceID option ->
    Ode.LowLevel.dConvexDataID ->
    Ode.LowLevel.convex_geom Ode.LowLevel.dGeomID = "ocamlode_dCreateConvex"
  external dGeomSetConvex :
    Ode.LowLevel.convex_geom Ode.LowLevel.dGeomID ->
    Ode.LowLevel.dConvexDataID -> unit = "ocamlode_dGeomSetConvex"
  external dConvexDataDestroy : Ode.LowLevel.dConvexDataID -> unit
    = "ocamlode_free_dConvexDataID"
  type dHeightfieldDataID
  external dGeomHeightfieldDataCreate :
    unit -> Ode.LowLevel.dHeightfieldDataID
    = "ocamlode_dGeomHeightfieldDataCreate"
  external dGeomHeightfieldDataDestroy :
    id:Ode.LowLevel.dHeightfieldDataID -> unit
    = "ocamlode_dGeomHeightfieldDataDestroy"
  external dCreateHeightfield :
    Ode.LowLevel.dSpaceID option ->
    data:Ode.LowLevel.dHeightfieldDataID ->
    placeable:bool -> Ode.LowLevel.heightfield_geom Ode.LowLevel.dGeomID
    = "ocamlode_dCreateHeightfield"
  external dGeomHeightfieldDataBuild :
    id:Ode.LowLevel.dHeightfieldDataID ->
    height_data:float array ->
    width:float ->
    depth:float ->
    width_samples:int ->
    depth_samples:int ->
    scale:float -> offset:float -> thickness:float -> wrap:bool -> unit
    = "ocamlode_dGeomHeightfieldDataBuild_bytecode"
    "ocamlode_dGeomHeightfieldDataBuild"
  external dGeomSetData : 'Ode.LowLevel.dGeomID -> int -> unit
    = "ocamlode_dGeomSetData"
  external dGeomGetData : 'Ode.LowLevel.dGeomID -> int
    = "ocamlode_dGeomGetData"
  external dGeomIsSpace : 'Ode.LowLevel.dGeomID -> bool
    = "ocamlode_dGeomIsSpace"
  external dGeomGetSpace : 'Ode.LowLevel.dGeomID -> Ode.LowLevel.dSpaceID
    = "ocamlode_dGeomGetSpace"
  external dGeomSetCategoryBits : 'Ode.LowLevel.dGeomID -> bits:int -> unit
    = "ocamlode_dGeomSetCategoryBits"
  external dGeomSetCollideBits : 'Ode.LowLevel.dGeomID -> bits:int -> unit
    = "ocamlode_dGeomSetCollideBits"
  external dGeomGetCategoryBits : 'Ode.LowLevel.dGeomID -> int
    = "ocamlode_dGeomGetCategoryBits"
  external dGeomGetCollideBits : 'Ode.LowLevel.dGeomID -> int
    = "ocamlode_dGeomGetCollideBits"
  external dGeomEnable : 'Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dGeomEnable"
  external dGeomDisable : 'Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dGeomDisable"
  external dGeomIsEnabled : 'Ode.LowLevel.dGeomID -> bool
    = "ocamlode_dGeomIsEnabled"
  external dGeomSetOffsetPosition :
    'Ode.LowLevel.dGeomID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dGeomSetOffsetPosition"
  external dGeomSetOffsetRotation :
    'Ode.LowLevel.dGeomID -> r:Ode.LowLevel.dMatrix3 -> unit
    = "ocamlode_dGeomSetOffsetRotation"
  external dGeomSetOffsetQuaternion :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dQuaternion -> unit
    = "ocamlode_dGeomSetOffsetQuaternion"
  external dGeomGetOffsetQuaternion :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dQuaternion
    = "ocamlode_dGeomGetOffsetQuaternion"
  external dGeomSetOffsetWorldPosition :
    'Ode.LowLevel.dGeomID -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dGeomSetOffsetWorldPosition"
  external dGeomSetOffsetWorldRotation :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dMatrix3 -> unit
    = "ocamlode_dGeomSetOffsetWorldRotation"
  external dGeomSetOffsetWorldQuaternion :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dQuaternion -> unit
    = "ocamlode_dGeomSetOffsetWorldQuaternion"
  external dGeomClearOffset : 'Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dGeomClearOffset"
  external dGeomIsOffset : 'Ode.LowLevel.dGeomID -> bool
    = "ocamlode_dGeomIsOffset"
  external dGeomGetOffsetPosition :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dVector3
    = "ocamlode_dGeomGetOffsetPosition"
  external dGeomGetOffsetRotation :
    'Ode.LowLevel.dGeomID -> Ode.LowLevel.dMatrix3
    = "ocamlode_dGeomGetOffsetRotation"
  external dMassCreate : unit -> Ode.LowLevel.dMass = "ocamlode_dMassCreate"
  external dMass_set_mass : Ode.LowLevel.dMass -> float -> unit
    = "ocamlode_dMass_set_mass"
  external dMass_mass : Ode.LowLevel.dMass -> float = "ocamlode_dMass_mass"
  external dMass_set_c : Ode.LowLevel.dMass -> Ode.LowLevel.dVector4 -> unit
    = "ocamlode_dMass_set_c"
  external dMass_c : Ode.LowLevel.dMass -> Ode.LowLevel.dVector4
    = "ocamlode_dMass_c"
  external dMass_set_I : Ode.LowLevel.dMass -> Ode.LowLevel.dMatrix3 -> unit
    = "ocamlode_dMass_set_I"
  external dMass_I : Ode.LowLevel.dMass -> Ode.LowLevel.dMatrix3
    = "ocamlode_dMass_I"
  external dMassSetZero : Ode.LowLevel.dMass -> unit
    = "ocamlode_dMassSetZero"
  external dMassSetParameters :
    Ode.LowLevel.dMass ->
    mass:float ->
    cgx:float ->
    cgy:float ->
    cgz:float ->
    i11:float ->
    i22:float -> i33:float -> i12:float -> i13:float -> i23:float -> unit
    = "ocamlode_dMassSetParameters_bc" "ocamlode_dMassSetParameters"
  external dMassSetSphere :
    Ode.LowLevel.dMass -> density:float -> radius:float -> unit
    = "ocamlode_dMassSetSphere"
  external dMassSetSphereTotal :
    Ode.LowLevel.dMass -> total_mass:float -> radius:float -> unit
    = "ocamlode_dMassSetSphereTotal"
  external dMassSetBox :
    Ode.LowLevel.dMass ->
    density:float -> lx:float -> ly:float -> lz:float -> unit
    = "ocamlode_dMassSetBox"
  external dMassSetBoxTotal :
    Ode.LowLevel.dMass ->
    total_mass:float -> lx:float -> ly:float -> lz:float -> unit
    = "ocamlode_dMassSetBoxTotal"
  type direction = Dir_x | Dir_y | Dir_z
  external dMassSetCapsule :
    Ode.LowLevel.dMass ->
    density:float ->
    direction:Ode.LowLevel.direction -> radius:float -> length:float -> unit
    = "ocamlode_dMassSetCapsule"
  external dMassSetCapsuleTotal :
    Ode.LowLevel.dMass ->
    total_mass:float ->
    direction:Ode.LowLevel.direction -> radius:float -> length:float -> unit
    = "ocamlode_dMassSetCapsuleTotal"
  external dMassSetCylinder :
    Ode.LowLevel.dMass ->
    density:float ->
    direction:Ode.LowLevel.direction -> radius:float -> length:float -> unit
    = "ocamlode_dMassSetCylinder"
  external dMassSetCylinderTotal :
    Ode.LowLevel.dMass ->
    total_mass:float ->
    direction:Ode.LowLevel.direction -> radius:float -> length:float -> unit
    = "ocamlode_dMassSetCylinderTotal"
  external dMassSetTrimesh :
    Ode.LowLevel.dMass ->
    density:float -> Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dMassSetTrimesh"
  external dMassSetTrimeshTotal :
    Ode.LowLevel.dMass ->
    total_mass:float ->
    Ode.LowLevel.trimesh_geom Ode.LowLevel.dGeomID -> unit
    = "ocamlode_dMassSetTrimeshTotal"
  external dMassCheck : Ode.LowLevel.dMass -> bool = "ocamlode_dMassCheck"
  external dMassAdjust : Ode.LowLevel.dMass -> float -> unit
    = "ocamlode_dMassAdjust"
  external dMassTranslate :
    Ode.LowLevel.dMass -> x:float -> y:float -> z:float -> unit
    = "ocamlode_dMassTranslate"
  external dMassRotate : Ode.LowLevel.dMass -> Ode.LowLevel.dMatrix3 -> unit
    = "ocamlode_dMassRotate"
  external dMassAdd : Ode.LowLevel.dMass -> Ode.LowLevel.dMass -> unit
    = "ocamlode_dMassAdd"
  external dRGetIdentity : unit -> Ode.LowLevel.dMatrix3
    = "ocamlode_dRSetIdentity"
  external dRFromAxisAndAngle :
    ax:float -> ay:float -> az:float -> angle:float -> Ode.LowLevel.dMatrix3
    = "ocamlode_dRFromAxisAndAngle"
  external dRFromEulerAngles :
    phi:float -> theta:float -> psi:float -> Ode.LowLevel.dMatrix3
    = "ocamlode_dRFromEulerAngles"
  external dQGetIdentity : unit -> Ode.LowLevel.dQuaternion
    = "ocamlode_dQSetIdentity"
  external dQFromAxisAndAngle :
    ax:float ->
    ay:float -> az:float -> angle:float -> Ode.LowLevel.dQuaternion
    = "ocamlode_dQFromAxisAndAngle"
  external dWorldImpulseToForce :
    Ode.LowLevel.dWorldID ->
    stepsize:float ->
    ix:float -> iy:float -> iz:float -> Ode.LowLevel.dVector3
    = "ocamlode_dWorldImpulseToForce"
  external dQtoR : Ode.LowLevel.dQuaternion -> Ode.LowLevel.dMatrix3
    = "ocamlode_dQtoR"
  external dPlaneSpace :
    n:Ode.LowLevel.dVector3 -> Ode.LowLevel.dVector3 * Ode.LowLevel.dVector3
    = "ocamlode_dPlaneSpace"
  val is_nan : float -> bool
  val dVALIDVEC3 : Ode.LowLevel.dVector3 -> bool
  val dVALIDVEC4 : Ode.LowLevel.dVector3 -> bool
  val dVALIDMAT3 : Ode.LowLevel.dMatrix3 -> bool
  val dVALIDMAT4 : Ode.LowLevel.dMatrix4 -> bool
  val dLENGTH : Ode.LowLevel.dVector3 -> float
  val dMULTIPLY0_331 :
    Ode.LowLevel.dMatrix3 -> Ode.LowLevel.dVector3 -> Ode.LowLevel.dVector3
  val dMULTIPLY0_333 :
    Ode.LowLevel.dMatrix3 -> Ode.LowLevel.dMatrix3 -> Ode.LowLevel.dMatrix3
  val dSafeNormalize3_ml : Ode.LowLevel.dVector3 -> Ode.LowLevel.dVector3
  external dSafeNormalize3_ode :
    Ode.LowLevel.dVector3 -> Ode.LowLevel.dVector3
    = "ocamlode_dSafeNormalize3"
  val dNormalize3 : Ode.LowLevel.dVector3 -> Ode.LowLevel.dVector3
  external dNormalize4 : Ode.LowLevel.dVector4 -> Ode.LowLevel.dVector4
    = "ocamlode_dSafeNormalize4"
  external dQNormalize4 :
    Ode.LowLevel.dQuaternion -> Ode.LowLevel.dQuaternion
    = "ocamlode_dSafeNormalize4"
  external dMaxDifference :
    a:Ode.LowLevel.dVector3 ->
    b:Ode.LowLevel.dVector3 -> n:int -> m:int -> float
    = "ocamlode_dMaxDifference"
  external dQMaxDifference :
    a:Ode.LowLevel.dQuaternion ->
    b:Ode.LowLevel.dQuaternion -> n:int -> m:int -> float
    = "ocamlode_dMaxDifference"
  external dMultiply0 : '-> '-> p:int -> q:int -> r:int -> float array
    = "ocamlode_dMultiply0"
  val dMultiply0_331 : Ode.LowLevel.dMatrix3 -> '-> Ode.LowLevel.dVector3
  val dMultiply0_333 : Ode.LowLevel.dMatrix3 -> '-> Ode.LowLevel.dMatrix3
  external memory_share : unit -> bool = "ocamlode_memory_share"
end