module Raylib.Types.Core.Text
(
FontType (..),
GlyphInfo (..),
Font (..),
p'glyphInfo'value,
p'glyphInfo'offsetX,
p'glyphInfo'offsetY,
p'glyphInfo'advanceX,
p'glyphInfo'image,
p'font'baseSize,
p'font'glyphCount,
p'font'glyphPadding,
p'font'texture,
p'font'recs,
p'font'glyphs,
)
where
import Foreign
( Ptr,
Storable (alignment, peek, poke, sizeOf),
castPtr,
newArray,
peekArray,
plusPtr,
)
import Foreign.C
( CInt (..),
)
import Raylib.Internal (Closeable(..))
import Raylib.Internal.Foreign (Freeable (rlFreeDependents), c'free, rlFree)
import Raylib.Types.Core (Rectangle)
import Raylib.Types.Core.Textures (Image, Texture, p'image'data)
data FontType = FontDefault | FontBitmap | FontSDF deriving (Int -> FontType
FontType -> Int
FontType -> [FontType]
FontType -> FontType
FontType -> FontType -> [FontType]
FontType -> FontType -> FontType -> [FontType]
(FontType -> FontType)
-> (FontType -> FontType)
-> (Int -> FontType)
-> (FontType -> Int)
-> (FontType -> [FontType])
-> (FontType -> FontType -> [FontType])
-> (FontType -> FontType -> [FontType])
-> (FontType -> FontType -> FontType -> [FontType])
-> Enum FontType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: FontType -> FontType
succ :: FontType -> FontType
$cpred :: FontType -> FontType
pred :: FontType -> FontType
$ctoEnum :: Int -> FontType
toEnum :: Int -> FontType
$cfromEnum :: FontType -> Int
fromEnum :: FontType -> Int
$cenumFrom :: FontType -> [FontType]
enumFrom :: FontType -> [FontType]
$cenumFromThen :: FontType -> FontType -> [FontType]
enumFromThen :: FontType -> FontType -> [FontType]
$cenumFromTo :: FontType -> FontType -> [FontType]
enumFromTo :: FontType -> FontType -> [FontType]
$cenumFromThenTo :: FontType -> FontType -> FontType -> [FontType]
enumFromThenTo :: FontType -> FontType -> FontType -> [FontType]
Enum)
data GlyphInfo = GlyphInfo
{ GlyphInfo -> Int
glyphInfo'value :: Int,
GlyphInfo -> Int
glyphInfo'offsetX :: Int,
GlyphInfo -> Int
glyphInfo'offsetY :: Int,
GlyphInfo -> Int
glyphInfo'advanceX :: Int,
GlyphInfo -> Image
glyphInfo'image :: Image
}
deriving (GlyphInfo -> GlyphInfo -> Bool
(GlyphInfo -> GlyphInfo -> Bool)
-> (GlyphInfo -> GlyphInfo -> Bool) -> Eq GlyphInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GlyphInfo -> GlyphInfo -> Bool
== :: GlyphInfo -> GlyphInfo -> Bool
$c/= :: GlyphInfo -> GlyphInfo -> Bool
/= :: GlyphInfo -> GlyphInfo -> Bool
Eq, Int -> GlyphInfo -> ShowS
[GlyphInfo] -> ShowS
GlyphInfo -> String
(Int -> GlyphInfo -> ShowS)
-> (GlyphInfo -> String)
-> ([GlyphInfo] -> ShowS)
-> Show GlyphInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GlyphInfo -> ShowS
showsPrec :: Int -> GlyphInfo -> ShowS
$cshow :: GlyphInfo -> String
show :: GlyphInfo -> String
$cshowList :: [GlyphInfo] -> ShowS
showList :: [GlyphInfo] -> ShowS
Show)
instance Storable GlyphInfo where
sizeOf :: GlyphInfo -> Int
sizeOf GlyphInfo
_ = Int
40
alignment :: GlyphInfo -> Int
alignment GlyphInfo
_ = Int
4
peek :: Ptr GlyphInfo -> IO GlyphInfo
peek Ptr GlyphInfo
_p = do
Int
value <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'value Ptr GlyphInfo
_p)
Int
offsetX <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetX Ptr GlyphInfo
_p)
Int
offsetY <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetY Ptr GlyphInfo
_p)
Int
advanceX <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'advanceX Ptr GlyphInfo
_p)
Image
image <- Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphInfo -> Ptr Image
p'glyphInfo'image Ptr GlyphInfo
_p)
GlyphInfo -> IO GlyphInfo
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (GlyphInfo -> IO GlyphInfo) -> GlyphInfo -> IO GlyphInfo
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> Int -> Image -> GlyphInfo
GlyphInfo Int
value Int
offsetX Int
offsetY Int
advanceX Image
image
poke :: Ptr GlyphInfo -> GlyphInfo -> IO ()
poke Ptr GlyphInfo
_p (GlyphInfo Int
value Int
offsetX Int
offsetY Int
advanceX Image
image) = do
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'value Ptr GlyphInfo
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
value)
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetX Ptr GlyphInfo
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetX)
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetY Ptr GlyphInfo
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetY)
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'advanceX Ptr GlyphInfo
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
advanceX)
Ptr Image -> Image -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphInfo -> Ptr Image
p'glyphInfo'image Ptr GlyphInfo
_p) Image
image
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
p'glyphInfo'value :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'value :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'value = (Ptr GlyphInfo -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)
p'glyphInfo'offsetX :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetX :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetX = (Ptr GlyphInfo -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4)
p'glyphInfo'offsetY :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetY :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'offsetY = (Ptr GlyphInfo -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)
p'glyphInfo'advanceX :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'advanceX :: Ptr GlyphInfo -> Ptr CInt
p'glyphInfo'advanceX = (Ptr GlyphInfo -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12)
p'glyphInfo'image :: Ptr GlyphInfo -> Ptr Image
p'glyphInfo'image :: Ptr GlyphInfo -> Ptr Image
p'glyphInfo'image = (Ptr GlyphInfo -> Int -> Ptr Image
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16)
instance Freeable GlyphInfo where
rlFreeDependents :: GlyphInfo -> Ptr GlyphInfo -> IO ()
rlFreeDependents GlyphInfo
_ Ptr GlyphInfo
ptr = Ptr () -> IO ()
c'free (Ptr () -> IO ()) -> (Ptr CUChar -> Ptr ()) -> Ptr CUChar -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr CUChar -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr CUChar -> IO ()) -> IO (Ptr CUChar) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr CUChar) -> IO (Ptr CUChar)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Image -> Ptr (Ptr CUChar)
p'image'data (Ptr GlyphInfo -> Ptr Image
p'glyphInfo'image Ptr GlyphInfo
ptr))
data Font = Font
{ Font -> Int
font'baseSize :: Int,
Font -> Int
font'glyphCount :: Int,
Font -> Int
font'glyphPadding :: Int,
Font -> Texture
font'texture :: Texture,
Font -> [Rectangle]
font'recs :: [Rectangle],
Font -> [GlyphInfo]
font'glyphs :: [GlyphInfo]
}
deriving (Font -> Font -> Bool
(Font -> Font -> Bool) -> (Font -> Font -> Bool) -> Eq Font
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Font -> Font -> Bool
== :: Font -> Font -> Bool
$c/= :: Font -> Font -> Bool
/= :: Font -> Font -> Bool
Eq, Int -> Font -> ShowS
[Font] -> ShowS
Font -> String
(Int -> Font -> ShowS)
-> (Font -> String) -> ([Font] -> ShowS) -> Show Font
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Font -> ShowS
showsPrec :: Int -> Font -> ShowS
$cshow :: Font -> String
show :: Font -> String
$cshowList :: [Font] -> ShowS
showList :: [Font] -> ShowS
Show)
instance Storable Font where
sizeOf :: Font -> Int
sizeOf Font
_ = Int
48
alignment :: Font -> Int
alignment Font
_ = Int
4
peek :: Ptr Font -> IO Font
peek Ptr Font
_p = do
Int
baseSize <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr CInt
p'font'baseSize Ptr Font
_p)
Int
glyphCount <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr CInt
p'font'glyphCount Ptr Font
_p)
Int
glyphPadding <- CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CInt -> Int) -> IO CInt -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr CInt
p'font'glyphPadding Ptr Font
_p)
Texture
texture <- Ptr Texture -> IO Texture
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr Texture
p'font'texture Ptr Font
_p)
[Rectangle]
recs <- Int -> Ptr Rectangle -> IO [Rectangle]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
glyphCount (Ptr Rectangle -> IO [Rectangle])
-> IO (Ptr Rectangle) -> IO [Rectangle]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Rectangle) -> IO (Ptr Rectangle)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr (Ptr Rectangle)
p'font'recs Ptr Font
_p)
[GlyphInfo]
glyphs <- Int -> Ptr GlyphInfo -> IO [GlyphInfo]
forall a. Storable a => Int -> Ptr a -> IO [a]
peekArray Int
glyphCount (Ptr GlyphInfo -> IO [GlyphInfo])
-> IO (Ptr GlyphInfo) -> IO [GlyphInfo]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr GlyphInfo) -> IO (Ptr GlyphInfo)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr (Ptr GlyphInfo)
p'font'glyphs Ptr Font
_p)
Font -> IO Font
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Font -> IO Font) -> Font -> IO Font
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> Texture -> [Rectangle] -> [GlyphInfo] -> Font
Font Int
baseSize Int
glyphCount Int
glyphPadding Texture
texture [Rectangle]
recs [GlyphInfo]
glyphs
poke :: Ptr Font -> Font -> IO ()
poke Ptr Font
_p (Font Int
baseSize Int
glyphCount Int
glyphPadding Texture
texture [Rectangle]
recs [GlyphInfo]
glyphs) = do
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Font -> Ptr CInt
p'font'baseSize Ptr Font
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
baseSize)
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Font -> Ptr CInt
p'font'glyphCount Ptr Font
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
glyphCount)
Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Font -> Ptr CInt
p'font'glyphPadding Ptr Font
_p) (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
glyphPadding)
Ptr Texture -> Texture -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Font -> Ptr Texture
p'font'texture Ptr Font
_p) Texture
texture
Ptr (Ptr Rectangle) -> Ptr Rectangle -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Font -> Ptr (Ptr Rectangle)
p'font'recs Ptr Font
_p) (Ptr Rectangle -> IO ()) -> IO (Ptr Rectangle) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [Rectangle] -> IO (Ptr Rectangle)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [Rectangle]
recs
Ptr (Ptr GlyphInfo) -> Ptr GlyphInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Font -> Ptr (Ptr GlyphInfo)
p'font'glyphs Ptr Font
_p) (Ptr GlyphInfo -> IO ()) -> IO (Ptr GlyphInfo) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [GlyphInfo] -> IO (Ptr GlyphInfo)
forall a. Storable a => [a] -> IO (Ptr a)
newArray [GlyphInfo]
glyphs
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
instance Closeable Font where
close :: Font -> IO ()
close Font
font = Texture -> IO ()
forall a. Closeable a => a -> IO ()
close (Font -> Texture
font'texture Font
font)
addToWindowResources :: WindowResources -> Font -> IO ()
addToWindowResources WindowResources
window Font
font = WindowResources -> Texture -> IO ()
forall a. Closeable a => WindowResources -> a -> IO ()
addToWindowResources WindowResources
window (Font -> Texture
font'texture Font
font)
p'font'baseSize :: Ptr Font -> Ptr CInt
p'font'baseSize :: Ptr Font -> Ptr CInt
p'font'baseSize = (Ptr Font -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0)
p'font'glyphCount :: Ptr Font -> Ptr CInt
p'font'glyphCount :: Ptr Font -> Ptr CInt
p'font'glyphCount = (Ptr Font -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4)
p'font'glyphPadding :: Ptr Font -> Ptr CInt
p'font'glyphPadding :: Ptr Font -> Ptr CInt
p'font'glyphPadding = (Ptr Font -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8)
p'font'texture :: Ptr Font -> Ptr Texture
p'font'texture :: Ptr Font -> Ptr Texture
p'font'texture = (Ptr Font -> Int -> Ptr Texture
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12)
p'font'recs :: Ptr Font -> Ptr (Ptr Rectangle)
p'font'recs :: Ptr Font -> Ptr (Ptr Rectangle)
p'font'recs = (Ptr Font -> Int -> Ptr (Ptr Rectangle)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32)
p'font'glyphs :: Ptr Font -> Ptr (Ptr GlyphInfo)
p'font'glyphs :: Ptr Font -> Ptr (Ptr GlyphInfo)
p'font'glyphs = (Ptr Font -> Int -> Ptr (Ptr GlyphInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40)
instance Freeable Font where
rlFreeDependents :: Font -> Ptr Font -> IO ()
rlFreeDependents Font
val Ptr Font
ptr = do
Ptr () -> IO ()
c'free (Ptr () -> IO ())
-> (Ptr Rectangle -> Ptr ()) -> Ptr Rectangle -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Rectangle -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (Ptr Rectangle -> IO ()) -> IO (Ptr Rectangle) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr Rectangle) -> IO (Ptr Rectangle)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr (Ptr Rectangle)
p'font'recs Ptr Font
ptr)
[GlyphInfo] -> Ptr [GlyphInfo] -> IO ()
forall a. Freeable a => a -> Ptr a -> IO ()
rlFree (Font -> [GlyphInfo]
font'glyphs Font
val) (Ptr [GlyphInfo] -> IO ())
-> (Ptr GlyphInfo -> Ptr [GlyphInfo]) -> Ptr GlyphInfo -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr GlyphInfo -> Ptr [GlyphInfo]
forall a b. Ptr a -> Ptr b
castPtr (Ptr GlyphInfo -> IO ()) -> IO (Ptr GlyphInfo) -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr GlyphInfo) -> IO (Ptr GlyphInfo)
forall a. Storable a => Ptr a -> IO a
peek (Ptr Font -> Ptr (Ptr GlyphInfo)
p'font'glyphs Ptr Font
ptr)