Skip to content
Snippets Groups Projects
Commit 3f441d02 authored by Jens Nolte's avatar Jens Nolte
Browse files

Add conversion functions for waylands `fixed` type

parent d80696e9
No related branches found
No related tags found
No related merge requests found
......@@ -126,11 +126,13 @@ test-suite quasar-wayland-test
type: exitcode-stdio-1.0
build-depends:
base,
--QuickCheck,
hspec,
--quasar-wayland,
inline-c,
quasar,
quasar-wayland,
QuickCheck,
main-is: Spec.hs
other-modules:
--Quasar.TemplateSpec
Quasar.Wayland.WlFixedSpec
hs-source-dirs:
test
......@@ -11,6 +11,8 @@ module Quasar.Wayland.Protocol (
-- ** Wayland types
WlFixed(..),
fixedToDouble,
doubleToFixed,
WlString(..),
toString,
......
......@@ -7,6 +7,8 @@ module Quasar.Wayland.Protocol.Core (
GenericNewId,
Opcode,
WlFixed(..),
fixedToDouble,
doubleToFixed,
WlString(..),
toString,
fromString,
......@@ -115,11 +117,17 @@ data GenericNewId = GenericNewId WlString Version Word32
-- | Signed 24.8 decimal numbers.
newtype WlFixed = WlFixed Word32
newtype WlFixed = WlFixed Int32
deriving newtype Eq
instance Show WlFixed where
show x = "[fixed " <> show x <> "]"
show (WlFixed x) = "[fixed " <> show x <> "]"
fixedToDouble :: WlFixed -> Double
fixedToDouble (WlFixed f) = fromIntegral f / 256
doubleToFixed :: Double -> WlFixed
doubleToFixed d = WlFixed (round (d * 256))
-- | A string. The encoding is not officially specified, but in practice UTF-8 is used.
......@@ -163,8 +171,8 @@ instance WireFormat Word32 where
showArgument = show
instance WireFormat WlFixed where
putArgument (WlFixed repr) = pure $ MessagePart (putWord32host repr) 4 mempty
getArgument = pure . WlFixed <$> getWord32host
putArgument (WlFixed repr) = pure $ MessagePart (putInt32host repr) 4 mempty
getArgument = pure . WlFixed <$> getInt32host
showArgument = show
instance WireFormat WlString where
......
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Quasar.Wayland.WlFixedSpec (spec) where
import Foreign.C.Types
import Language.C.Inline qualified as C
import Language.C.Inline.Unsafe qualified as CU
import Quasar.Prelude
import Quasar.Wayland.Protocol (WlFixed(..), fixedToDouble, doubleToFixed)
import System.IO.Unsafe (unsafeDupablePerformIO)
import Test.Hspec
import Test.QuickCheck
deriving newtype instance Arbitrary WlFixed
C.include "<stdint.h>"
-- Libwayland implementation wl_fixed_to_double
-- https://github.com/wayland-project/wayland/blob/5e4253ed50cfc9a132b5231f68a7084e0c3dc417/src/wayland-util.h#L596-L644
libwaylandFixedToDouble :: WlFixed -> Double
libwaylandFixedToDouble (WlFixed value) = unsafeDupablePerformIO do
CDouble result <- [CU.block|
double {
union {
double d;
int64_t i;
} u;
u.i = ((1023LL + 44LL) << 52) + (1LL << 51) + $(int32_t value);
return u.d - (3LL << 43);
}
|]
pure result
-- Libwayland implementation wl_fixed_from_double
-- https://github.com/wayland-project/wayland/blob/5e4253ed50cfc9a132b5231f68a7084e0c3dc417/src/wayland-util.h#L596-L644
libwaylandDoubleToFixed :: Double -> WlFixed
libwaylandDoubleToFixed (CDouble -> value) = WlFixed $ unsafeDupablePerformIO
[CU.block|
int32_t {
union {
double d;
int64_t i;
} u;
u.d = $(double value) + (3LL << (51 - 8));
return (int32_t)u.i;
}
|]
spec :: Spec
spec = do
describe "fixedToDouble and doubleToFixed" do
it "produces the same value when passing through both functions" $ property \value -> do
doubleToFixed (fixedToDouble value) `shouldBe` value
describe "fixedToDouble" do
it "behaves like wl_fixed_to_double" $ property \value -> do
fixedToDouble value `shouldBe` libwaylandFixedToDouble value
it "is correct when interacting with wl_fixed_from_double" $ property \value -> do
libwaylandDoubleToFixed (fixedToDouble value) `shouldBe` value
describe "doubleToFixed" do
it "behaves like wl_fixed_from_double" $ property \value -> do
doubleToFixed value `shouldBe` libwaylandDoubleToFixed value
it "is correct when interacting with wl_fixed_to_double" $ property \value -> do
doubleToFixed (libwaylandFixedToDouble value) `shouldBe` value
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment