{-# LANGUAGE CApiFFI #-}
-- | Internal C routines which need to be QuickCheck tested.
module Graphics.Text.Font.Choose.Internal.Test where
import Foreign.C.String (CString)
import Foreign.Ptr (Ptr)
import Data.MessagePack (MessagePack)
import Graphics.Text.Font.Choose.Internal.FFI
-- | A C test function which transcodes data into & out of FontConfig datastructures.
type RoundTrip = CString -> Int -> Ptr Int -> CString
-- | Test a roundtrip function, the output should be equal to the input
-- (wrapped in a Maybe type).
roundtrip :: MessagePack a => RoundTrip -> a -> Maybe a
roundtrip fn = fromMessage . withMessage fn
-- | C test function for StrSet type.
foreign import capi "transcode.h" testStrSet :: RoundTrip
-- | C test function for CharSet type.
foreign import capi "transcode.h" testCharSet :: RoundTrip
-- | C test function for LangSet type.
foreign import capi "transcode.h" testLangSet :: RoundTrip
-- | C test function for Range type.
foreign import capi "transcode.h" testRange :: RoundTrip
-- | C test function for Matrix type.
foreign import capi "transcode.h" testMatrix :: RoundTrip
-- | C test function for Value type.
foreign import capi "transcode.h" testValue :: RoundTrip
-- | C test function for Pattern type.
foreign import capi "transcode.h" testPattern :: RoundTrip
-- | C test function for FontSet type.
foreign import capi "transcode.h" testFontSet :: RoundTrip