-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | SFML bindings
--
-- Low level bindings for SFML 2.3.2.
@package SFML
@version 2.3.2.4
module SFML.Window.JoystickIdentification
-- | Joystick's identification
data JoystickIdentification
JoystickIdentification :: String -> Int -> Int -> JoystickIdentification
name :: JoystickIdentification -> String
vendorId :: JoystickIdentification -> Int
productId :: JoystickIdentification -> Int
instance Eq JoystickIdentification
instance Show JoystickIdentification
instance Storable JoystickIdentification
module SFML.Window.WindowHandle
newtype WindowHandle
WindowHandle :: (Ptr WindowHandle) -> WindowHandle
module SFML.SFDisplayable
class SFDisplayable a
display :: SFDisplayable a => a -> IO ()
module SFML.Graphics.FontInfo
data FontInfo
FontInfo :: String -> FontInfo
family :: FontInfo -> String
instance Show FontInfo
instance Storable FontInfo
module SFML.SFCopyable
class SFCopyable a
copy :: SFCopyable a => a -> IO a
module SFML.System.InputStream
-- | Function to read data from the stream.
type InputStreamReadFunc a = Ptr Char -> Word64 -> Ptr a -> IO Word64
-- | Function to set the current read position.
type InputStreamSeekFunc a = Word64 -> Ptr a -> IO Word64
-- | Function to get the current read position.
type InputStreamTellFunc a = Ptr a -> IO Word64
-- | Function to get the total number of bytes in the stream.
type InputStreamGetSizeFunc a = Ptr a -> IO Word64
-- | Set of callbacks that allow users to define custom file streams.
data InputStream
InputStream :: Ptr (InputStreamReadFunc a) -> Ptr (InputStreamSeekFunc a) -> Ptr (InputStreamTellFunc a) -> Ptr (InputStreamGetSizeFunc a) -> Ptr a -> InputStream
read :: InputStream -> Ptr (InputStreamReadFunc a)
seek :: InputStream -> Ptr (InputStreamSeekFunc a)
tell :: InputStream -> Ptr (InputStreamTellFunc a)
getSize :: InputStream -> Ptr (InputStreamGetSizeFunc a)
userData :: InputStream -> Ptr a
instance Show InputStream
instance Storable InputStream
module SFML.SFResource
class SFResource a
destroy :: SFResource a => a -> IO ()
module SFML.SFException
data SFException
SFException :: String -> SFException
instance Typeable SFException
instance Show SFException
instance Exception SFException
module SFML.Utils
-- | Run the given IO action and throw an error if it fails.
err :: Exception e => IO (Either e a) -> IO a
-- | Potentially tag a Maybe value with an error.
tagErr :: e -> Maybe a -> Either e a
module SFML.Window.VideoMode
data VideoMode
VideoMode :: Int -> Int -> Int -> VideoMode
-- | Video mode width, in pixels
windowWidth :: VideoMode -> Int
-- | Video mode height, in pixels
windowHeight :: VideoMode -> Int
-- | Video mode pixel depth, in bits per pixels
windowBPP :: VideoMode -> Int
-- | Get the current desktop video mode
getDesktopMode :: IO VideoMode
-- | Retrieve all the video modes supported in fullscreen mode
--
-- When creating a fullscreen window, the video mode is restricted to be
-- compatible with what the graphics driver and monitor support.
getFullscreenModes :: IO [VideoMode]
-- | Tell whether or not a video mode is valid
--
-- The validity of video modes is only relevant when using fullscreen
-- windows; otherwise any video mode can be used with no restriction.
isValid :: VideoMode -> IO Bool
instance Show VideoMode
instance Storable VideoMode
module SFML.Window.Types
newtype Context
Context :: (Ptr Context) -> Context
newtype Window
Window :: (Ptr Window) -> Window
module SFML.Window.Keyboard
-- | Key codes.
data KeyCode
-- | The A key
KeyA :: KeyCode
-- | The B key
KeyB :: KeyCode
-- | The C key
KeyC :: KeyCode
-- | The D key
KeyD :: KeyCode
-- | The E key
KeyE :: KeyCode
-- | The F key
KeyF :: KeyCode
-- | The G key
KeyG :: KeyCode
-- | The H key
KeyH :: KeyCode
-- | The I key
KeyI :: KeyCode
-- | The J key
KeyJ :: KeyCode
-- | The K key
KeyK :: KeyCode
-- | The L key
KeyL :: KeyCode
-- | The M key
KeyM :: KeyCode
-- | The N key
KeyN :: KeyCode
-- | The O key
KeyO :: KeyCode
-- | The P key
KeyP :: KeyCode
-- | The Q key
KeyQ :: KeyCode
-- | The R key
KeyR :: KeyCode
-- | The S key
KeyS :: KeyCode
-- | The T key
KeyT :: KeyCode
-- | The U key
KeyU :: KeyCode
-- | The V key
KeyV :: KeyCode
-- | The W key
KeyW :: KeyCode
-- | The X key
KeyX :: KeyCode
-- | The Y key
KeyY :: KeyCode
-- | The Z key
KeyZ :: KeyCode
-- | The 0 key
KeyNum0 :: KeyCode
-- | The 1 key
KeyNum1 :: KeyCode
-- | The 2 key
KeyNum2 :: KeyCode
-- | The 3 key
KeyNum3 :: KeyCode
-- | The 4 key
KeyNum4 :: KeyCode
-- | The 5 key
KeyNum5 :: KeyCode
-- | The 6 key
KeyNum6 :: KeyCode
-- | The 7 key
KeyNum7 :: KeyCode
-- | The 8 key
KeyNum8 :: KeyCode
-- | The 9 key
KeyNum9 :: KeyCode
-- | The Escape key
KeyEscape :: KeyCode
-- | The left Control key
KeyLControl :: KeyCode
-- | The left Shift key
KeyLShift :: KeyCode
-- | The left Alt key
KeyLAlt :: KeyCode
-- | The left OS specific key: window (Windows and Linux), apple (MacOS X),
-- ...
KeyLSystem :: KeyCode
-- | The right Control key
KeyRControl :: KeyCode
-- | The right Shift key
KeyRShift :: KeyCode
-- | The right Alt key
KeyRAlt :: KeyCode
-- | The right OS specific key: window (Windows and Linux), apple (MacOS
-- X), ...
KeyRSystem :: KeyCode
-- | The Menu key
KeyMenu :: KeyCode
-- | The [ key
KeyLBracket :: KeyCode
-- | The ] key
KeyRBracket :: KeyCode
-- | The ; key
KeySemiColon :: KeyCode
-- | The , key
KeyComma :: KeyCode
-- | The . key
KeyPeriod :: KeyCode
-- | The ' key
KeyQuote :: KeyCode
-- | The / key
KeySlash :: KeyCode
-- | The key
KeyBackSlash :: KeyCode
-- | The ~ key
KeyTilde :: KeyCode
-- | The = key
KeyEqual :: KeyCode
-- | The - key
KeyDash :: KeyCode
-- | The Space key
KeySpace :: KeyCode
-- | The Return key
KeyReturn :: KeyCode
-- | The Backspace key
KeyBack :: KeyCode
-- | The Tabulation key
KeyTab :: KeyCode
-- | The Page up key
KeyPageUp :: KeyCode
-- | The Page down key
KeyPageDown :: KeyCode
-- | The End key
KeyEnd :: KeyCode
-- | The Home key
KeyHome :: KeyCode
-- | The Insert key
KeyInsert :: KeyCode
-- | The Delete key
KeyDelete :: KeyCode
-- | +
KeyAdd :: KeyCode
-- |
KeySubtract :: KeyCode
-- |
KeyMultiply :: KeyCode
-- | /
KeyDivide :: KeyCode
-- | Left arrow
KeyLeft :: KeyCode
-- | Right arrow
KeyRight :: KeyCode
-- | Up arrow
KeyUp :: KeyCode
-- | Down arrow
KeyDown :: KeyCode
-- | The numpad 0 key
KeyNumpad0 :: KeyCode
-- | The numpad 1 key
KeyNumpad1 :: KeyCode
-- | The numpad 2 key
KeyNumpad2 :: KeyCode
-- | The numpad 3 key
KeyNumpad3 :: KeyCode
-- | The numpad 4 key
KeyNumpad4 :: KeyCode
-- | The numpad 5 key
KeyNumpad5 :: KeyCode
-- | The numpad 6 key
KeyNumpad6 :: KeyCode
-- | The numpad 7 key
KeyNumpad7 :: KeyCode
-- | The numpad 8 key
KeyNumpad8 :: KeyCode
-- | The numpad 9 key
KeyNumpad9 :: KeyCode
-- | The F1 key
KeyF1 :: KeyCode
-- | The F2 key
KeyF2 :: KeyCode
-- | The F3 key
KeyF3 :: KeyCode
-- | The F4 key
KeyF4 :: KeyCode
-- | The F5 key
KeyF5 :: KeyCode
-- | The F6 key
KeyF6 :: KeyCode
-- | The F7 key
KeyF7 :: KeyCode
-- | The F8 key
KeyF8 :: KeyCode
-- | The F8 key
KeyF9 :: KeyCode
-- | The F10 key
KeyF10 :: KeyCode
-- | The F11 key
KeyF11 :: KeyCode
-- | The F12 key
KeyF12 :: KeyCode
-- | The F13 key
KeyF13 :: KeyCode
-- | The F14 key
KeyF14 :: KeyCode
-- | The F15 key
KeyF15 :: KeyCode
-- | The Pause key
KeyPause :: KeyCode
-- | Undefined key
Undefined :: KeyCode
-- | Check if a key is pressed
isKeyPressed :: KeyCode -> IO Bool
instance Eq KeyCode
instance Enum KeyCode
instance Bounded KeyCode
instance Show KeyCode
instance Storable KeyCode
module SFML.Window.Joystick
-- | Global joysticks capabilities
data JoystickCap
-- | Maximum number of supported joysticks
JoystickCount :: JoystickCap
-- | Maximum number of supported buttons
JoystickButtonCount :: JoystickCap
-- | Maximum number of supported axes
JoystickAxisCount :: JoystickCap
-- | Axes supported by SFML joysticks
data JoystickAxis
-- | The X axis
JoystickX :: JoystickAxis
-- | The Y axis
JoystickY :: JoystickAxis
-- | The Z axis
JoystickZ :: JoystickAxis
-- | The R axis
JoystickR :: JoystickAxis
-- | The U axis
JoystickU :: JoystickAxis
-- | The V axis
JoystickV :: JoystickAxis
-- | The X axis of the point-of-view hat
JoystickPovX :: JoystickAxis
-- | The Y axis of the point-of-view hat
JoystickPovY :: JoystickAxis
-- | Check if a joystick is connected.
isJoystickConnected :: Int -> IO Bool
-- | Return the number of buttons supported by a joystick.
--
-- If the joystick is not connected, this function returns 0.
getButtonCount :: Int -> IO Int
-- | Check if a joystick supports a given axis.
--
-- If the joystick is not connected, this function returns False.
hasAxis :: Int -> Int -> IO Bool
-- | Check if a joystick button is pressed.
--
-- If the joystick is not connected, this function returns False.
isJoystickButtonPressed :: Int -> Int -> IO Bool
-- | Get the current position of a joystick axis.
--
-- If the joystick is not connected, this function returns 0.
getAxisPosition :: Int -> Int -> IO Float
-- | Get the joystick information.
--
-- The result of this function will only remain valid until the next time
-- the function is called.
getJoystickIdentification :: Int -> IO JoystickIdentification
-- | Update the states of all joysticks.
--
-- This function is used internally by SFML, so you normally don't have
-- to call it explicitely. However, you may need to call it if you have
-- no window yet (or no window at all): in this case the joysticks states
-- are not updated automatically.
updateJoystick :: IO ()
instance Eq JoystickCap
instance Bounded JoystickCap
instance Show JoystickCap
instance Eq JoystickAxis
instance Enum JoystickAxis
instance Bounded JoystickAxis
instance Show JoystickAxis
instance Storable JoystickAxis
instance Enum JoystickCap
module SFML.Window.ContextSettings
data ContextSettings
ContextSettings :: Int -> Int -> Int -> Int -> Int -> [ContextAttribute] -> ContextSettings
-- | Bits of the depth buffer
depthBits :: ContextSettings -> Int
-- | Bits of the stencil buffer
stencilBits :: ContextSettings -> Int
-- | Level of antialiasing
antialiasingLevel :: ContextSettings -> Int
-- | Major number of the context version to create
majorVersion :: ContextSettings -> Int
-- | Minor number of the context version to create
minorVersion :: ContextSettings -> Int
-- | The attribute flags to create the context with
attributeFlags :: ContextSettings -> [ContextAttribute]
data ContextAttribute
-- | Non-debug, compatibility context (this and the core attribute are
-- mutually exclusive)
ContextDefault :: ContextAttribute
-- | Core attribute
ContextCore :: ContextAttribute
-- | Debug attribute
ContextDebug :: ContextAttribute
instance Eq ContextAttribute
instance Show ContextAttribute
instance Show ContextSettings
instance Enum ContextAttribute
instance Storable ContextSettings
module SFML.Window.Context
-- | Create a new context.
--
-- This function activates the new context.
createContext :: IO Context
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Activate or deactivate explicitely a context.
setActiveContext :: Context -> Bool -> IO ()
instance SFResource Context
module SFML.System.Vector3
data Vec3f
Vec3f :: {-# UNPACK #-} !Float -> {-# UNPACK #-} !Float -> {-# UNPACK #-} !Float -> Vec3f
instance Show Vec3f
instance Storable Vec3f
module SFML.System.Vector2
data Vec2i
Vec2i :: {-# UNPACK #-} !Int -> {-# UNPACK #-} !Int -> Vec2i
data Vec2u
Vec2u :: {-# UNPACK #-} !Word -> {-# UNPACK #-} !Word -> Vec2u
data Vec2f
Vec2f :: {-# UNPACK #-} !Float -> {-# UNPACK #-} !Float -> Vec2f
instance Show Vec2i
instance Show Vec2u
instance Show Vec2f
instance Fractional Vec2f
instance Num Vec2f
instance Storable Vec2f
instance Num Vec2u
instance Storable Vec2u
instance Num Vec2i
instance Storable Vec2i
module SFML.Window.Mouse
data MouseButton
MouseLeft :: MouseButton
MouseRight :: MouseButton
MouseMiddle :: MouseButton
MouseXButton1 :: MouseButton
MouseXButton2 :: MouseButton
data MouseWheel
-- | The vertical mouse wheel
MouseVerticalWheel :: MouseWheel
-- | The horizontal mouse wheel
MouseHorizontalWheel :: MouseWheel
-- | Check if a mouse button is pressed.
isMouseButtonPressed :: MouseButton -> IO Bool
instance Eq MouseButton
instance Enum MouseButton
instance Bounded MouseButton
instance Show MouseButton
instance Eq MouseWheel
instance Enum MouseWheel
instance Bounded MouseWheel
instance Show MouseWheel
instance Storable MouseButton
instance Storable MouseWheel
module SFML.Window.Event
data SFEvent
SFEvtClosed :: SFEvent
SFEvtResized :: Int -> Int -> SFEvent
width :: SFEvent -> Int
height :: SFEvent -> Int
SFEvtLostFocus :: SFEvent
SFEvtGainedFocus :: SFEvent
SFEvtTextEntered :: String -> SFEvent
text :: SFEvent -> String
SFEvtKeyPressed :: KeyCode -> Bool -> Bool -> Bool -> Bool -> SFEvent
code :: SFEvent -> KeyCode
alt :: SFEvent -> Bool
ctrl :: SFEvent -> Bool
shift :: SFEvent -> Bool
sys :: SFEvent -> Bool
SFEvtKeyReleased :: KeyCode -> Bool -> Bool -> Bool -> Bool -> SFEvent
code :: SFEvent -> KeyCode
alt :: SFEvent -> Bool
ctrl :: SFEvent -> Bool
shift :: SFEvent -> Bool
sys :: SFEvent -> Bool
SFEvtMouseWheelMoved :: Int -> Int -> Int -> SFEvent
moveDelta :: SFEvent -> Int
x :: SFEvent -> Int
y :: SFEvent -> Int
SFEvtMouseWheelScrolled :: MouseWheel -> Float -> Int -> Int -> SFEvent
wheel :: SFEvent -> MouseWheel
scrollDelta :: SFEvent -> Float
x :: SFEvent -> Int
y :: SFEvent -> Int
SFEvtMouseButtonPressed :: MouseButton -> Int -> Int -> SFEvent
button :: SFEvent -> MouseButton
x :: SFEvent -> Int
y :: SFEvent -> Int
SFEvtMouseButtonReleased :: MouseButton -> Int -> Int -> SFEvent
button :: SFEvent -> MouseButton
x :: SFEvent -> Int
y :: SFEvent -> Int
SFEvtMouseMoved :: Int -> Int -> SFEvent
x :: SFEvent -> Int
y :: SFEvent -> Int
SFEvtMouseEntered :: SFEvent
SFEvtMouseLeft :: SFEvent
SFEvtJoystickButtonPressed :: Int -> Int -> SFEvent
joystickId :: SFEvent -> Int
joystickBt :: SFEvent -> Int
SFEvtJoystickButtonReleased :: Int -> Int -> SFEvent
joystickId :: SFEvent -> Int
joystickBt :: SFEvent -> Int
SFEvtJoystickMoved :: Int -> JoystickAxis -> Float -> SFEvent
joystickId :: SFEvent -> Int
joystickAxis :: SFEvent -> JoystickAxis
position :: SFEvent -> Float
SFEvtJoystickConnected :: Int -> SFEvent
joystickId :: SFEvent -> Int
SFEvtJoystickDisconnected :: Int -> SFEvent
joystickId :: SFEvent -> Int
instance Eq SFEvent
instance Show SFEvent
instance Storable SFEvent
module SFML.Window.SFWindow
class (SFResource a, SFDisplayable a) => SFWindow a
close :: SFWindow a => a -> IO ()
isWindowOpen :: SFWindow a => a -> IO Bool
getWindowSettings :: SFWindow a => a -> IO ContextSettings
pollEvent :: SFWindow a => a -> IO (Maybe SFEvent)
waitEvent :: SFWindow a => a -> IO (Maybe SFEvent)
getWindowPosition :: SFWindow a => a -> IO Vec2i
setWindowPosition :: SFWindow a => a -> Vec2i -> IO ()
getWindowSize :: SFWindow a => a -> IO Vec2u
setWindowSize :: SFWindow a => a -> Vec2u -> IO ()
setWindowTitle :: SFWindow a => a -> String -> IO ()
setWindowIcon :: SFWindow a => a -> Int -> Int -> Ptr b -> IO ()
setWindowVisible :: SFWindow a => a -> Bool -> IO ()
setMouseVisible :: SFWindow a => a -> Bool -> IO ()
setVSync :: SFWindow a => a -> Bool -> IO ()
setKeyRepeat :: SFWindow a => a -> Bool -> IO ()
setWindowActive :: SFWindow a => a -> Bool -> IO ()
requestFocus :: SFWindow a => a -> IO ()
hasFocus :: SFWindow a => a -> IO Bool
setFramerateLimit :: SFWindow a => a -> Int -> IO ()
setJoystickThreshold :: SFWindow a => a -> Float -> IO ()
getSystemHandle :: SFWindow a => a -> IO WindowHandle
getMousePosition :: SFWindow a => Maybe a -> IO Vec2i
setMousePosition :: SFWindow a => Vec2i -> Maybe a -> IO ()
module SFML.Window.Window
data WindowStyle
-- | No border / title bar (this flag and all others are mutually
-- exclusive)
SFNone :: WindowStyle
-- | Title bar + fixed border
SFTitlebar :: WindowStyle
-- | Titlebar + resizable border + maximize button
SFResize :: WindowStyle
-- | Titlebar + close button
SFClose :: WindowStyle
-- | Fullscreen mode (this flag and all others are mutually exclusive)
SFFullscreen :: WindowStyle
-- | Default window style
SFDefaultStyle :: WindowStyle
-- | Construct a new window.
--
-- This function creates the window with the size and pixel depth defined
-- in a mode. An optional style can be passed to customize the look and
-- behaviour of the window (borders, title bar, resizable, closable,
-- ...). If a style contains sfFullscreen, then a mode must be a valid
-- video mode.
--
-- The fourth parameter is a pointer to a structure specifying advanced
-- OpenGL context settings such as antialiasing, depth-buffer bits, etc.
createWindow :: VideoMode -> String -> [WindowStyle] -> Maybe ContextSettings -> IO Window
-- | Construct a window from an existing control.
--
-- Use this constructor if you want to create an OpenGL rendering area
-- into an already existing control.
--
-- The second parameter is a pointer to a structure specifying advanced
-- OpenGL context settings such as antialiasing, depth-buffer bits, etc.
windowFromHandle :: WindowHandle -> Maybe ContextSettings -> IO Window
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Close the window.
--
-- After calling this function, the window object remains valid; you must
-- call destroy to actually delete it.
close :: SFWindow a => a -> IO ()
-- | Tell whether or not a window is opened
--
-- This function returns whether or not the window exists.
--
-- Note that a hidden window (setWindowVisible False ) will return
-- True.
isWindowOpen :: SFWindow a => a -> IO Bool
-- | Get the settings of the OpenGL context of a window.
--
-- Note that these settings may be different from what was passed to the
-- window create function, if one or more settings were not supported. In
-- this case, SFML chose the closest match.
getWindowSettings :: SFWindow a => a -> IO ContextSettings
-- | Pop the event on top of events stack, if any, and return it.
--
-- This function is not blocking: if there's no pending event then it
-- will return false and leave a event unmodified. Note that more than
-- one event may be present in the events stack, thus you should always
-- call this function in a loop to make sure that you process every
-- pending event.
pollEvent :: SFWindow a => a -> IO (Maybe SFEvent)
-- | Wait for an event and return it.
--
-- This function is blocking: if there's no pending event then it will
-- wait until an event is received.
--
-- After this function returns (and no error occured), the event object
-- is always valid and filled properly.
--
-- This function is typically used when you have a thread that is
-- dedicated to events handling: you want to make this thread sleep as
-- long as no new event is received.
waitEvent :: SFWindow a => a -> IO (Maybe SFEvent)
-- | Get the position of a window.
getWindowPosition :: SFWindow a => a -> IO Vec2i
-- | Change the position of a window on screen.
--
-- This function only works for top-level windows (i.e. it will be
-- ignored for windows created from the handle of a child
-- window/control).
setWindowPosition :: SFWindow a => a -> Vec2i -> IO ()
-- | Get the size of the rendering region of a window.
--
-- The size doesn't include the titlebar and borders of the window.
getWindowSize :: SFWindow a => a -> IO Vec2u
-- | Change the size of the rendering region of a window.
setWindowSize :: SFWindow a => a -> Vec2u -> IO ()
-- | Change the title of a window.
setWindowTitle :: SFWindow a => a -> String -> IO ()
-- | Change a window's icon.
--
-- Pixels must be an array of width x height pixels in 32-bits RGBA
-- format.
setWindowIcon :: SFWindow a => a -> Int -> Int -> Ptr b -> IO ()
-- | Show or hide a window.
setWindowVisible :: SFWindow a => a -> Bool -> IO ()
-- | Show or hide the mouse cursor.
setMouseVisible :: SFWindow a => a -> Bool -> IO ()
-- | Enable or disable vertical synchronization. Activating vertical
-- synchronization will limit the number of frames displayed to the
-- refresh rate of the monitor.
--
-- This can avoid some visual artifacts, and limit the framerate to a
-- good value (but not constant across different computers).
setVSync :: SFWindow a => a -> Bool -> IO ()
-- | Enable or disable automatic key-repeat.
--
-- If key repeat is enabled, you will receive repeated KeyPress events
-- while keeping a key pressed. If it is disabled, you will only get a
-- single event when the key is pressed.
--
-- Key repeat is enabled by default.
setKeyRepeat :: SFWindow a => a -> Bool -> IO ()
-- | Activate or deactivate a window as the current target for OpenGL
-- rendering.
--
-- A window is active only on the current thread, if you want to make it
-- active on another thread you have to deactivate it on the previous
-- thread first if it was active.
--
-- Only one window can be active on a thread at a time, thus the window
-- previously active (if any) automatically gets deactivated.
setWindowActive :: SFWindow a => a -> Bool -> IO ()
-- | Request the current window to be made the active foreground window.
--
-- At any given time, only one window may have the input focus to receive
-- input events such as keystrokes or mouse events. If a window requests
-- focus, it only hints to the operating system, that it would like to be
-- focused. The operating system is free to deny the request. This is not
-- to be confused with setWindowActive.
requestFocus :: SFWindow a => a -> IO ()
-- | Check whether the render window has the input focus.
--
-- At any given time, only one window may have the input focus to receive
-- input events such as keystrokes or most mouse events.
hasFocus :: SFWindow a => a -> IO Bool
-- | Update the target's contents.
display :: SFDisplayable a => a -> IO ()
-- | Limit the framerate to a maximum fixed frequency.
--
-- If a limit is set, the window will use a small delay after each call
-- to display to ensure that the current frame lasted long enough
-- to match the framerate limit.
setFramerateLimit :: SFWindow a => a -> Int -> IO ()
-- | Change the joystick threshold.
--
-- The joystick threshold is the value below which no JoyMoved event will
-- be generated.
setJoystickThreshold :: SFWindow a => a -> Float -> IO ()
-- | Get the OS-specific handle of the window.
--
-- The type of the returned handle is WindowHandle, which is a
-- typedef to the handle type defined by the OS.
--
-- You shouldn't need to use this function, unless you have very specific
-- stuff to implement that SFML doesn't support, or implement a temporary
-- workaround until a bug is fixed.
getSystemHandle :: SFWindow a => a -> IO WindowHandle
-- | Get the current position of the mouse
--
-- This function returns the current position of the mouse cursor
-- relative to the given window, or desktop if Nothing is passed.
getMousePosition :: SFWindow a => Maybe a -> IO Vec2i
-- | Set the current position of the mouse
--
-- This function sets the current position of the mouse cursor relative
-- to the given window, or desktop if Nothing is passed.
setMousePosition :: SFWindow a => Vec2i -> Maybe a -> IO ()
instance Eq WindowStyle
instance Bounded WindowStyle
instance Show WindowStyle
instance SFWindow Window
instance SFDisplayable Window
instance SFResource Window
instance Enum WindowStyle
module SFML.System.Time
type Time = Int64
-- | Predefined "zero" time value.
timeZero :: Time
-- | Return a time value as a number of seconds.
asSeconds :: Time -> Float
-- | Return a time value as a number of milliseconds.
asMilliseconds :: Time -> Int
-- | Return a time value as a number of microseconds.
asMicroseconds :: Time -> Int64
-- | Construct a time value from a number of seconds.
seconds :: Float -> Time
-- | Construct a time value from a number of milliseconds.
milliseconds :: Int -> Time
-- | Construct a time value from a number of microseconds.
microseconds :: Int64 -> Time
module SFML.Audio.SFSoundBuffer
class SFSoundBuffer a
getChannelCount :: SFSoundBuffer a => a -> IO Int
getDuration :: SFSoundBuffer a => a -> IO Time
module SFML.System.Sleep
-- | Make the current thread sleep for a given duration.
--
-- sfSleep is the best way to block a program or one of its threads, as
-- it doesn't consume any CPU power.
sfSleep :: Time -> IO ()
module SFML.System.Clock
newtype Clock
Clock :: (Ptr Clock) -> Clock
-- | Create a new clock and start it.
createClock :: IO Clock
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Get the time elapsed in a clock.
--
-- This function returns the time elapsed since the last call to
-- sfClock_restart (or the construction of the object if sfClock_restart
-- has not been called).
getElapsedTime :: Clock -> IO Time
-- | Restart a clock.
--
-- This function puts the time counter back to zero. It also returns the
-- time elapsed since the clock was started.
restartClock :: Clock -> IO Time
instance SFResource Clock
instance SFCopyable Clock
module SFML.System
module SFML.Window
module SFML.Graphics.Types
newtype CircleShape
CircleShape :: (Ptr CircleShape) -> CircleShape
newtype ConvexShape
ConvexShape :: (Ptr ConvexShape) -> ConvexShape
newtype Font
Font :: (Ptr Font) -> Font
newtype Image
Image :: (Ptr Image) -> Image
newtype Shader
Shader :: (Ptr Shader) -> Shader
newtype RectangleShape
RectangleShape :: (Ptr RectangleShape) -> RectangleShape
newtype RenderTexture
RenderTexture :: (Ptr RenderTexture) -> RenderTexture
newtype RenderWindow
RenderWindow :: (Ptr RenderWindow) -> RenderWindow
newtype Shape
Shape :: (Ptr Shape) -> Shape
newtype Sprite
Sprite :: (Ptr Sprite) -> Sprite
newtype Text
Text :: (Ptr Text) -> Text
newtype Texture
Texture :: (Ptr Texture) -> Texture
newtype VertexArray
VertexArray :: (Ptr VertexArray) -> VertexArray
newtype View
View :: (Ptr View) -> View
instance Storable Shader
instance Storable Texture
module SFML.Graphics.SFSmoothTexture
class SFSmoothTexture a
setSmooth :: SFSmoothTexture a => a -> Bool -> IO ()
isSmooth :: SFSmoothTexture a => a -> IO Bool
module SFML.Graphics.SFShapeResizable
class SFShapeResizable a
setPointCount :: SFShapeResizable a => a -> Int -> IO ()
module SFML.Graphics.SFCoordSpace
class SFCoordSpace a
mapPixelToCoords :: SFCoordSpace a => a -> Vec2i -> Maybe View -> IO Vec2f
module SFML.Graphics.SFBindable
class SFBindable a
bind :: SFBindable a => a -> IO ()
module SFML.Graphics.Rect
-- | Utility class for manipulating rectangles.
data FloatRect
FloatRect :: Float -> Float -> Float -> Float -> FloatRect
fleft :: FloatRect -> Float
ftop :: FloatRect -> Float
fwidth :: FloatRect -> Float
fheight :: FloatRect -> Float
-- | Utility class for manipulating rectangles.
data IntRect
IntRect :: Int -> Int -> Int -> Int -> IntRect
ileft :: IntRect -> Int
itop :: IntRect -> Int
iwidth :: IntRect -> Int
iheight :: IntRect -> Int
class Rect a
intersectRect :: Rect a => a -> a -> Maybe a
-- | Check if a point is inside a rectangle's area.
floatRectContains :: Float -> Float -> FloatRect -> Bool
-- | Check if a point is inside a rectangle's area.
intRectContains :: Int -> Int -> IntRect -> Bool
instance Rect IntRect
instance Rect FloatRect
instance Storable IntRect
instance Storable FloatRect
module SFML.Graphics.SFBounded
class SFBounded a
getLocalBounds :: SFBounded a => a -> IO FloatRect
getGlobalBounds :: SFBounded a => a -> IO FloatRect
module SFML.Graphics.SFViewable
class SFViewable a
setView :: SFViewable a => a -> View -> IO ()
getView :: SFViewable a => a -> IO View
getDefaultView :: SFViewable a => a -> IO View
getViewport :: SFViewable a => a -> View -> IO IntRect
module SFML.Graphics.Texture
-- | A null texture.
nullTexture :: Texture
-- | Create a new texture.
createTexture :: Int -> Int -> IO (Either SFException Texture)
-- | Create a new texture from a file.
textureFromFile :: FilePath -> Maybe IntRect -> IO (Either SFException Texture)
-- | Create a new texture from a file in memory.
textureFromMemory :: Ptr a -> Int -> Maybe IntRect -> IO (Either SFException Texture)
-- | Create a new texture from a custom stream.
textureFromStream :: InputStream -> Maybe IntRect -> IO (Either SFException Texture)
-- | Create a new texture from an image.
textureFromImage :: Image -> Maybe IntRect -> IO (Either SFException Texture)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Return the size of the texture in pixels.
textureSize :: Texture -> IO Vec2u
-- | Copy a texture's pixels to an image
copyTextureToImage :: Texture -> IO Image
-- | Update a texture from an array of pixels.
updateTextureFromPixels :: Texture -> Ptr a -> Int -> Int -> Int -> Int -> IO ()
-- | Update a texture from an image.
updateTextureFromImage :: Texture -> Image -> Int -> Int -> IO ()
-- | Update a texture from the contents of a window.
updateTextureFromWindow :: Texture -> Window -> Int -> Int -> IO ()
-- | Update a texture from the contents of a render-window.
updateTextureFromRenderWindow :: Texture -> RenderWindow -> Int -> Int -> IO ()
-- | Bind the resource for rendering (activate it).
--
-- This function is not part of the graphics API, it mustn't be used when
-- drawing SFML entities. It must be used only if you mix sfShader with
-- OpenGL code.
bind :: SFBindable a => a -> IO ()
-- | Enable or disable the smooth filter on a texture.
setSmooth :: SFSmoothTexture a => a -> Bool -> IO ()
-- | Tell whether the smooth filter is enabled or not for a texture.
isSmooth :: SFSmoothTexture a => a -> IO Bool
-- | Enable or disable repeating for a texture.
--
-- Repeating is involved when using texture coordinates outside the
-- texture rectangle [0, 0, width, height]. In this case, if repeat mode
-- is enabled, the whole texture will be repeated as many times as needed
-- to reach the coordinate (for example, if the X texture coordinate is 3
-- * width, the texture will be repeated 3 times). If repeat mode is
-- disabled, the "extra space" will instead be filled with border pixels.
--
-- Warning: on very old graphics cards, white pixels may appear when the
-- texture is repeated. With such cards, repeat mode can be used reliably
-- only if the texture has power-of-two dimensions (such as 256x128).
-- Repeating is disabled by default.
setRepeated :: Texture -> Bool -> IO ()
-- | Tell whether a texture is repeated or not
isRepeated :: Texture -> IO Bool
-- | The maximum texture size allowed in pixels.
textureMaxSize :: Int
instance SFSmoothTexture Texture
instance SFBindable Texture
instance SFResource Texture
instance SFCopyable Texture
module SFML.Graphics.Transform
-- | Encapsulate a 3x3 transform matrix.
data Transform
m00 :: Transform -> Float
m10 :: Transform -> Float
m20 :: Transform -> Float
m01 :: Transform -> Float
m11 :: Transform -> Float
m21 :: Transform -> Float
m02 :: Transform -> Float
m12 :: Transform -> Float
m22 :: Transform -> Float
-- | Create a new transform from a matrix.
createTransform :: Float -> Float -> Float -> Float -> Float -> Float -> Float -> Float -> Float -> Transform
-- | Identity transform.
idTransform :: Transform
-- | Create a translation.
translation :: Float -> Float -> Transform
-- | Create a rotation.
rotation :: Float -> Transform
-- | Create a rotation.
--
-- The center of rotation is provided for convenience as a second
-- argument, so that you can build rotations around arbitrary points more
-- easily (and efficiently) than the usual [translate(-center),
-- rotate(angle), translate(center)].
rotationWithCenter :: Float -> Float -> Float -> Transform
-- | Create a scaling.
scaling :: Float -> Float -> Transform
-- | Create a scaling.
--
-- The center of scaling is provided for convenience as a second
-- argument, so that you can build scaling around arbitrary points more
-- easily (and efficiently) than the usual [translate(-center),
-- scale(factors), translate(center)]
scalingWithCenter :: Float -> Float -> Float -> Float -> Transform
-- | Return the inverse of a transform.
--
-- If the inverse cannot be computed, a new identity transform is
-- returned.
inverse :: Transform -> Transform
-- | Return the inverse of a transform.
--
-- This function is only applicable when the transform is composed of
-- rotations and translations only.
fastInverse :: Transform -> Transform
-- | Apply a transform to a 2D point.
transformPoint :: Transform -> Vec2f -> Vec2f
-- | Apply a transform to a 2D direction vector.
transformDir :: Transform -> Vec2f -> Vec2f
-- | Apply a transform to a rectangle.
--
-- Since SFML doesn't provide support for oriented rectangles, the result
-- of this function is always an axis-aligned rectangle, which means that
-- if the transform contains a rotation, the bounding rectangle of the
-- transformed rectangle is returned.
transformRect :: Transform -> FloatRect -> FloatRect
instance Num Transform
instance Storable Transform
module SFML.Graphics.SFTransformable
class SFTransformable a
setPosition :: SFTransformable a => a -> Vec2f -> IO ()
setRotation :: SFTransformable a => a -> Float -> IO ()
setScale :: SFTransformable a => a -> Vec2f -> IO ()
setOrigin :: SFTransformable a => a -> Vec2f -> IO ()
getPosition :: SFTransformable a => a -> IO Vec2f
getRotation :: SFTransformable a => a -> IO Float
getScale :: SFTransformable a => a -> IO Vec2f
getOrigin :: SFTransformable a => a -> IO Vec2f
move :: SFTransformable a => a -> Vec2f -> IO ()
rotate :: SFTransformable a => a -> Float -> IO ()
scale :: SFTransformable a => a -> Vec2f -> IO ()
getTransform :: SFTransformable a => a -> IO Transform
getInverseTransform :: SFTransformable a => a -> IO Transform
module SFML.Graphics.View
-- | Create a default view.
--
-- This function creates a default view of (0, 0, 1000, 1000)
createView :: IO View
-- | Construct a view from a rectangle
viewFromRect :: FloatRect -> IO View
-- | Copy an existing view.
copyView :: View -> IO View
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set the center of a view.
setViewCenter :: View -> Vec2f -> IO ()
-- | Set the size of a view.
setViewSize :: View -> Vec2f -> IO ()
-- | Set the orientation of a view.
--
-- The default rotation of a view is 0 degrees.
setViewRotation :: View -> Float -> IO ()
-- | Set the target viewport of a view
--
-- The viewport is the rectangle into which the contents of the view are
-- displayed, expressed as a factor (between 0 and 1) of the size of the
-- render target to which the view is applied. For example, a view which
-- takes the left side of the target would be defined by a rect of (0, 0,
-- 0.5, 1).
--
-- By default, a view has a viewport which covers the entire target.
setViewport :: View -> FloatRect -> IO ()
-- | Reset a view to the given rectangle.
--
-- Note that this function resets the rotation angle to 0.
resetView :: View -> FloatRect -> IO ()
-- | Get the center of a view.
getViewCenter :: View -> IO Vec2f
-- | Get the size of a view.
getViewSize :: View -> IO Vec2f
-- | Get the current orientation of a view, in degrees.
getViewRotation :: View -> IO Float
-- | Get the target viewport rectangle of a view, expressed as a factor of
-- the target size.
getViewViewport :: View -> IO FloatRect
-- | Move a view relatively to its current position.
moveView :: View -> Vec2f -> IO ()
-- | Rotate a view relatively to its current orientation.
rotateView :: View -> Float -> IO ()
-- | Resize a view rectangle relatively to its current size
--
-- Resizing the view simulates a zoom, as the zone displayed on screen
-- grows or shrinks.
--
-- factor is a multiplier:
--
--
-- - 1 keeps the size unchanged
-- - > 1 makes the view bigger (objects appear smaller)
-- - < 1 makes the view smaller (objects appear bigger)
--
zoomView :: View -> Float -> IO ()
instance SFResource View
module SFML.Graphics.PrimitiveType
-- | Types of primitives that a sf::VertexArray can render.
--
-- Points and lines have no area, therefore their thickness will always
-- be 1 pixel, regardless of the current transform and view.
data PrimitiveType
-- | List of individual points
Points :: PrimitiveType
-- | List of individual lines
Lines :: PrimitiveType
-- | List of connected lines, a point uses the previous point to form a
-- line
LineStrip :: PrimitiveType
-- | List of individual triangles
Triangles :: PrimitiveType
-- | List of connected triangles, a point uses the two previous points to
-- form a triangle
TriangleStrip :: PrimitiveType
-- | List of connected triangles, a point uses the common center and the
-- previous point to form a triangle
TriangleFan :: PrimitiveType
-- | List of individual quads
Quads :: PrimitiveType
instance Eq PrimitiveType
instance Enum PrimitiveType
instance Bounded PrimitiveType
instance Show PrimitiveType
instance Storable PrimitiveType
module SFML.Graphics.Glyph
-- | Describes a glyph (a visual character).
data Glyph
Glyph :: Int -> IntRect -> IntRect -> Glyph
-- | Offset to move horizontically to the next character
advance :: Glyph -> Int
-- | Bounding rectangle of the glyph, in coordinates relative to the
-- baseline
bounds :: Glyph -> IntRect
-- | Texture coordinates of the glyph inside the font's image
textureRect :: Glyph -> IntRect
instance Storable Glyph
module SFML.Graphics.Font
-- | Create a new font from a file.
fontFromFile :: FilePath -> IO (Either SFException Font)
-- | Create a new image font a file in memory.
fontFromMemory :: Ptr Char -> Int -> IO (Either SFException Font)
-- | Create a new image font a custom stream.
fontFromStream :: InputStream -> IO (Either SFException Font)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Get a glyph in a font.
getGlyph :: Font -> Int -> Int -> Bool -> IO Glyph
-- | Get the kerning value corresponding to a given pair of characters in a
-- font.
getKerning :: Font -> Int -> Int -> Int -> IO Float
-- | Get the line spacing value.
getLineSpacing :: Font -> Int -> IO Float
-- | Get the position of the underline.
--
-- Underline position is the vertical offset to apply between the
-- baseline and the underline.
getUnderlinePosition :: Font -> Int -> IO Float
-- | Get the thickness of the underline.
--
-- Underline thickness is the vertical size of the underline.
getUnderlineThickness :: Font -> Int -> IO Float
-- | Get the texture containing the glyphs of a given size in a font.
getFontTexture :: Font -> Int -> IO Texture
-- | Get the font information.
--
-- The returned structure will remain valid only if the font is still
-- valid. If the font is invalid an invalid structure is returned.
getInfo :: Font -> IO FontInfo
instance SFResource Font
instance SFCopyable Font
module SFML.Graphics.Color
-- | Utility data type for manpulating RGBA colors.
data Color
Color :: Word8 -> Word8 -> Word8 -> Word8 -> Color
r :: Color -> Word8
g :: Color -> Word8
b :: Color -> Word8
a :: Color -> Word8
black :: Color
white :: Color
red :: Color
green :: Color
blue :: Color
yellow :: Color
magenta :: Color
cyan :: Color
transparent :: Color
instance Eq Color
instance Show Color
instance Num Color
instance Storable Color
module SFML.Graphics.Image
-- | Create an image.
--
-- This image is filled with black pixels.
createImage :: Int -> Int -> IO (Either SFException Image)
-- | Create an image and fill it with a unique color.
imageFromColor :: Int -> Int -> Color -> IO Image
-- | Create an image from an array of pixels.
--
-- The pixel array is assumed to contain 32-bits RGBA pixels, and have
-- the given width and height. If not, this is an undefined behaviour.
--
-- If pixels is null, an empty image is created.
imageFromPixels :: Int -> Int -> Ptr a -> IO Image
-- | Create an image from a file on disk.
imageFromFile :: FilePath -> IO (Maybe Image)
-- | Create an image from a file in memory.
--
-- The supported image formats are bmp, png, tga, jpg, gif, psd, hdr and
-- pic. Some format options are not supported, like progressive jpeg.
--
-- If this function fails, the image is left unchanged.
imageFromMemory :: Ptr a -> Int -> IO (Maybe Image)
-- | Create an image from a custom stream.
--
-- The supported image formats are bmp, png, tga, jpg, gif, psd, hdr and
-- pic. Some format options are not supported, like progressive jpeg.
--
-- If this function fails, the image is left unchanged.
imageFromStream :: InputStream -> IO (Maybe Image)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Save an image to a file on disk.
--
-- The format of the image is automatically deduced from the extension.
-- The supported image formats are bmp, png, tga and jpg. The destination
-- file is overwritten if it already exists. This function fails if the
-- image is empty.
--
-- Return True if saving was successful.
saveImage :: Image -> FilePath -> IO Bool
-- | Return the size of an image in pixels.
imageSize :: Image -> IO Vec2u
-- | Create a transparency mask from a specified color-key.
--
-- This function sets the alpha value of every pixel matching the given
-- color to alpha (0 by default), so that they become transparent.
createMaskFromColor :: Image -> Color -> Int -> IO ()
-- | Copy pixels from an image onto another
--
-- This function does a slow pixel copy and should not be used
-- intensively. It can be used to prepare a complex static image from
-- several others, but if you need this kind of feature in real-time
-- you'd better use sfRenderTexture.
--
-- If sourceRect is empty, the whole image is copied. If applyAlpha is
-- set to true, the transparency of source pixels is applied. If it is
-- false, the pixels are copied unchanged with their alpha value.
copyImage' :: Image -> Image -> Int -> Int -> IntRect -> Bool -> IO ()
-- | Change the color of a pixel in an image.
--
-- This function doesn't check the validity of the pixel coordinates,
-- using out-of-range values will result in an undefined behaviour.
setPixel :: Image -> Int -> Int -> Color -> IO ()
-- | Get the color of a pixel in an image.
--
-- This function doesn't check the validity of the pixel coordinates,
-- using out-of-range values will result in an undefined behaviour.
getPixel :: Image -> Int -> Int -> IO Color
-- | Get a read-only pointer to the array of pixels of an image.
--
-- The returned value points to an array of RGBA pixels made of 8 bits
-- integers components. The size of the array is getWidth() * getHeight()
-- * 4.
--
-- Warning: the returned pointer may become invalid if you modify the
-- image, so you should never store it for too long. If the image is
-- empty, a null pointer is returned.
getPixels :: Image -> IO (Ptr a)
-- | Flip an image horizontally (left - right).
flipHorizontally :: Image -> IO ()
-- | Flip an image vertically (top - bottom)
flipVertically :: Image -> IO ()
instance SFResource Image
instance SFCopyable Image
module SFML.Graphics.SFShape
class SFShape a
setFillColor :: SFShape a => a -> Color -> IO ()
setOutlineColor :: SFShape a => a -> Color -> IO ()
setOutlineThickness :: SFShape a => a -> Float -> IO ()
getFillColor :: SFShape a => a -> IO Color
getOutlineColor :: SFShape a => a -> IO Color
getOutlineThickness :: SFShape a => a -> IO Float
getPointCount :: SFShape a => a -> IO Int
getPoint :: SFShape a => a -> Int -> IO Vec2f
module SFML.Graphics.SFTexturable
class SFTexturable a
setTexture :: SFTexturable a => a -> Texture -> Bool -> IO ()
setTextureRect :: SFTexturable a => a -> IntRect -> IO ()
getTexture :: SFTexturable a => a -> IO (Maybe Texture)
getTextureRect :: SFTexturable a => a -> IO IntRect
module SFML.Graphics.ConvexShape
-- | Create a new convex shape.
createConvexShape :: IO (Either SFException ConvexShape)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set the position of a transformable.
--
-- This function completely overwrites the previous position.
--
-- See move to apply an offset based on the previous position
-- instead.
--
-- The default position of a transformable object is (0, 0).
setPosition :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the orientation of a transformable.
--
-- This function completely overwrites the previous rotation.
--
-- See rotate to add an angle based on the previous rotation
-- instead.
--
-- The default rotation of a transformable SFTransformable object is 0.
setRotation :: SFTransformable a => a -> Float -> IO ()
-- | Set the scale factors of a transformable.
--
-- This function completely overwrites the previous scale.
--
-- See scale to add a factor based on the previous scale instead.
--
-- The default scale of a transformable SFTransformable object is (1, 1).
setScale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the local origin of a transformable.
--
-- The origin of an object defines the center point for all
-- transformations (position, scale, rotation).
--
-- The coordinates of this point must be relative to the top-left corner
-- of the object, and ignore all transformations (position, scale,
-- rotation).
--
-- The default origin of a transformable SFTransformable object is (0,
-- 0).
setOrigin :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the position of a transformable.
getPosition :: SFTransformable a => a -> IO Vec2f
-- | Get the orientation of a transformable.
getRotation :: SFTransformable a => a -> IO Float
-- | Get the current scale of a transformable
getScale :: SFTransformable a => a -> IO Vec2f
-- | Get the local origin of a transformable.
getOrigin :: SFTransformable a => a -> IO Vec2f
-- | Move a transformable by a given offset
--
-- This function adds to the current position of the object, unlike
-- setPosition which overwrites it.
move :: SFTransformable a => a -> Vec2f -> IO ()
-- | Rotate a transformable.
--
-- This function adds to the current rotation of the object, unlike
-- setRotation which overwrites it.
rotate :: SFTransformable a => a -> Float -> IO ()
-- | Scale a transformable.
--
-- This function multiplies the current scale of the object, unlike
-- setScale which overwrites it.
scale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the combined transform of a transformable.
getTransform :: SFTransformable a => a -> IO Transform
-- | Get the inverse of the combined transform of a transformable.
getInverseTransform :: SFTransformable a => a -> IO Transform
-- | Change the source texture of a Texturable.
--
-- The texture argument refers to a texture that must exist as long as
-- the texturable uses it. Indeed, the texturable doesn't store its own
-- copy of the texture, but rather keeps a pointer to the one that you
-- passed to this function.
--
-- If the source texture is destroyed and the texturable tries to use it,
-- the behaviour is undefined.
--
-- If resetRect is True, the TextureRect property of the
-- texturable is automatically adjusted to the size of the new texture.
-- If it is false, the texture rect is left unchanged.
setTexture :: SFTexturable a => a -> Texture -> Bool -> IO ()
-- | Set the sub-rectangle of the texture that a texturable will display.
--
-- The texture rect is useful when you don't want to display the whole
-- texture, but rather a part of it.
--
-- By default, the texture rect covers the entire texture.
setTextureRect :: SFTexturable a => a -> IntRect -> IO ()
-- | Get the source texture of a texturable.
--
-- If the texturable has no source texture, Nothing is returned.
--
-- The returned pointer is const, which means that you can't modify the
-- texture when you retrieve it with this function.
getTexture :: SFTexturable a => a -> IO (Maybe Texture)
-- | Get the sub-rectangle of the texture displayed by a texturable.
getTextureRect :: SFTexturable a => a -> IO IntRect
-- | Set the fill color of a shape.
--
-- This color is modulated (multiplied) with the shape's texture if any.
-- It can be used to colorize the shape, or change its global opacity.
--
-- You can use Transparent to make the inside of the shape
-- transparent, and have the outline alone.
--
-- By default, the shape's fill color is opaque white.
setFillColor :: SFShape a => a -> Color -> IO ()
-- | Set the outline color of a shape.
--
-- You can use Transparent to disable the outline.
--
-- By default, the shape's outline color is opaque white.
setOutlineColor :: SFShape a => a -> Color -> IO ()
-- | Set the thickness of a shape's outline.
--
-- This number cannot be negative. Using zero disables the outline.
--
-- By default, the outline thickness is 0.
setOutlineThickness :: SFShape a => a -> Float -> IO ()
-- | Get the fill color of a shape.
getFillColor :: SFShape a => a -> IO Color
-- | Get the outline color of a shape.
getOutlineColor :: SFShape a => a -> IO Color
-- | Get the outline thickness of a shape.
getOutlineThickness :: SFShape a => a -> IO Float
-- | Get the total number of points of a shape.
getPointCount :: SFShape a => a -> IO Int
-- | Get the ith point of a shape.
--
-- The result is undefined if index is out of the valid range.
getPoint :: SFShape a => a -> Int -> IO Vec2f
-- | Set the number of points of a resizable shape.
setPointCount :: SFShapeResizable a => a -> Int -> IO ()
-- | Set the position of a point in a convex shape.
--
-- Don't forget that the polygon must remain convex, and the points need
-- to stay ordered!
--
-- setPointCount must be called first in order to set the total
-- number of points. The result is undefined if the index is out of the
-- valid range.
setPoint :: ConvexShape -> Int -> Vec2f -> IO ()
-- | Get the local bounding rectangle of a boundable.
--
-- The returned rectangle is in local coordinates, which means that it
-- ignores the transformations (translation, rotation, scale, ...) that
-- are applied to the entity. In other words, this function returns the
-- bounds of the entity in the entity's coordinate system.
getLocalBounds :: SFBounded a => a -> IO FloatRect
-- | Get the global bounding rectangle of a shape.
--
-- The returned rectangle is in global coordinates, which means that it
-- takes in account the transformations (translation, rotation, scale,
-- ...) that are applied to the entity. In other words, this function
-- returns the bounds of the sprite in the global 2D world's coordinate
-- system.
getGlobalBounds :: SFBounded a => a -> IO FloatRect
instance SFBounded ConvexShape
instance SFShapeResizable ConvexShape
instance SFShape ConvexShape
instance SFTexturable ConvexShape
instance SFTransformable ConvexShape
instance SFResource ConvexShape
instance SFCopyable ConvexShape
module SFML.Graphics.RectangleShape
-- | Create a new rectangle shape.
createRectangleShape :: IO (Either SFException RectangleShape)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set the position of a transformable.
--
-- This function completely overwrites the previous position.
--
-- See move to apply an offset based on the previous position
-- instead.
--
-- The default position of a transformable object is (0, 0).
setPosition :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the orientation of a transformable.
--
-- This function completely overwrites the previous rotation.
--
-- See rotate to add an angle based on the previous rotation
-- instead.
--
-- The default rotation of a transformable SFTransformable object is 0.
setRotation :: SFTransformable a => a -> Float -> IO ()
-- | Set the scale factors of a transformable.
--
-- This function completely overwrites the previous scale.
--
-- See scale to add a factor based on the previous scale instead.
--
-- The default scale of a transformable SFTransformable object is (1, 1).
setScale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the local origin of a transformable.
--
-- The origin of an object defines the center point for all
-- transformations (position, scale, rotation).
--
-- The coordinates of this point must be relative to the top-left corner
-- of the object, and ignore all transformations (position, scale,
-- rotation).
--
-- The default origin of a transformable SFTransformable object is (0,
-- 0).
setOrigin :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the position of a transformable.
getPosition :: SFTransformable a => a -> IO Vec2f
-- | Get the orientation of a transformable.
getRotation :: SFTransformable a => a -> IO Float
-- | Get the current scale of a transformable
getScale :: SFTransformable a => a -> IO Vec2f
-- | Get the local origin of a transformable.
getOrigin :: SFTransformable a => a -> IO Vec2f
-- | Move a transformable by a given offset
--
-- This function adds to the current position of the object, unlike
-- setPosition which overwrites it.
move :: SFTransformable a => a -> Vec2f -> IO ()
-- | Rotate a transformable.
--
-- This function adds to the current rotation of the object, unlike
-- setRotation which overwrites it.
rotate :: SFTransformable a => a -> Float -> IO ()
-- | Scale a transformable.
--
-- This function multiplies the current scale of the object, unlike
-- setScale which overwrites it.
scale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the combined transform of a transformable.
getTransform :: SFTransformable a => a -> IO Transform
-- | Get the inverse of the combined transform of a transformable.
getInverseTransform :: SFTransformable a => a -> IO Transform
-- | Change the source texture of a Texturable.
--
-- The texture argument refers to a texture that must exist as long as
-- the texturable uses it. Indeed, the texturable doesn't store its own
-- copy of the texture, but rather keeps a pointer to the one that you
-- passed to this function.
--
-- If the source texture is destroyed and the texturable tries to use it,
-- the behaviour is undefined.
--
-- If resetRect is True, the TextureRect property of the
-- texturable is automatically adjusted to the size of the new texture.
-- If it is false, the texture rect is left unchanged.
setTexture :: SFTexturable a => a -> Texture -> Bool -> IO ()
-- | Set the sub-rectangle of the texture that a texturable will display.
--
-- The texture rect is useful when you don't want to display the whole
-- texture, but rather a part of it.
--
-- By default, the texture rect covers the entire texture.
setTextureRect :: SFTexturable a => a -> IntRect -> IO ()
-- | Get the source texture of a texturable.
--
-- If the texturable has no source texture, Nothing is returned.
--
-- The returned pointer is const, which means that you can't modify the
-- texture when you retrieve it with this function.
getTexture :: SFTexturable a => a -> IO (Maybe Texture)
-- | Get the sub-rectangle of the texture displayed by a texturable.
getTextureRect :: SFTexturable a => a -> IO IntRect
-- | Set the fill color of a shape.
--
-- This color is modulated (multiplied) with the shape's texture if any.
-- It can be used to colorize the shape, or change its global opacity.
--
-- You can use Transparent to make the inside of the shape
-- transparent, and have the outline alone.
--
-- By default, the shape's fill color is opaque white.
setFillColor :: SFShape a => a -> Color -> IO ()
-- | Set the outline color of a shape.
--
-- You can use Transparent to disable the outline.
--
-- By default, the shape's outline color is opaque white.
setOutlineColor :: SFShape a => a -> Color -> IO ()
-- | Set the thickness of a shape's outline.
--
-- This number cannot be negative. Using zero disables the outline.
--
-- By default, the outline thickness is 0.
setOutlineThickness :: SFShape a => a -> Float -> IO ()
-- | Get the fill color of a shape.
getFillColor :: SFShape a => a -> IO Color
-- | Get the outline color of a shape.
getOutlineColor :: SFShape a => a -> IO Color
-- | Get the outline thickness of a shape.
getOutlineThickness :: SFShape a => a -> IO Float
-- | Get the total number of points of a shape.
getPointCount :: SFShape a => a -> IO Int
-- | Get the ith point of a shape.
--
-- The result is undefined if index is out of the valid range.
getPoint :: SFShape a => a -> Int -> IO Vec2f
-- | Set the number of points of a resizable shape.
setPointCount :: SFShapeResizable a => a -> Int -> IO ()
-- | Set the size of a rectangle shape.
setSize :: RectangleShape -> Vec2f -> IO ()
-- | Get the size of a rectangle shape.
getSize :: RectangleShape -> IO Vec2f
-- | Get the local bounding rectangle of a boundable.
--
-- The returned rectangle is in local coordinates, which means that it
-- ignores the transformations (translation, rotation, scale, ...) that
-- are applied to the entity. In other words, this function returns the
-- bounds of the entity in the entity's coordinate system.
getLocalBounds :: SFBounded a => a -> IO FloatRect
-- | Get the global bounding rectangle of a shape.
--
-- The returned rectangle is in global coordinates, which means that it
-- takes in account the transformations (translation, rotation, scale,
-- ...) that are applied to the entity. In other words, this function
-- returns the bounds of the sprite in the global 2D world's coordinate
-- system.
getGlobalBounds :: SFBounded a => a -> IO FloatRect
instance SFBounded RectangleShape
instance SFShape RectangleShape
instance SFTexturable RectangleShape
instance SFTransformable RectangleShape
instance SFResource RectangleShape
instance SFCopyable RectangleShape
module SFML.Graphics.Shader
-- | A null shader.
nullShader :: Shader
-- | Load both the vertex and fragment shaders from files.
--
-- This function can load both the vertex and the fragment shaders, or
-- only one of them: pass Nothing if you don't want to load either
-- the vertex shader or the fragment shader.
--
-- The sources must be text files containing valid shaders in GLSL
-- language. GLSL is a C-like language dedicated to OpenGL shaders;
-- you'll probably need to read a good documentation for it before
-- writing your own shaders.
shaderFromFile :: Maybe FilePath -> Maybe FilePath -> IO (Either SFException Shader)
-- | Load both the vertex and fragment shaders from source codes in memory.
--
-- This function can load both the vertex and the fragment shaders, or
-- only one of them: pass Nothing if you don't want to load either
-- the vertex shader or the fragment shader.
--
-- The sources must be valid shaders in GLSL language. GLSL is a C-like
-- language dedicated to OpenGL shaders; you'll probably need to read a
-- good documentation for it before writing your own shaders.
shaderFromMemory :: Maybe String -> Maybe String -> IO (Either SFException Shader)
-- | Load both the vertex and fragment shaders from custom streams.
--
-- This function can load both the vertex and the fragment shaders, or
-- only one of them: pass Nothing if you don't want to load either
-- the vertex shader or the fragment shader.
--
-- The source codes must be valid shaders in GLSL language. GLSL is a
-- C-like language dedicated to OpenGL shaders; you'll probably need to
-- read a good documentation for it before writing your own shaders.
shaderFromStream :: Maybe InputStream -> Maybe InputStream -> IO (Either SFException Shader)
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Change a float parameter of a shader.
setFloatParameter :: Shader -> String -> Float -> IO ()
-- | Change a 2-components vector parameter of a shader.
setFloat2Parameter :: Shader -> String -> Float -> Float -> IO ()
-- | Change a 3-components vector parameter of a shader.
setFloat3Parameter :: Shader -> String -> Float -> Float -> Float -> IO ()
-- | Change a 4-components vector parameter of a shader.
setFloat4Parameter :: Shader -> String -> Float -> Float -> Float -> Float -> IO ()
-- | Change a 2-components vector parameter of a shader.
setVector2Parameter :: Shader -> String -> Vec2f -> IO ()
-- | Change a 3-components vector parameter of a shader.
setVector3Parameter :: Shader -> String -> Vec3f -> IO ()
-- | Change a color parameter of a shader.
setColorParameter :: Shader -> String -> Color -> IO ()
-- | Change a matrix parameter of a shader.
setTransformParameter :: Shader -> String -> Transform -> IO ()
-- | Change a texture parameter of a shader.
--
-- The corresponding parameter in the shader must be a 2D texture
-- (sampler2D GLSL type).
setTextureParameter :: Shader -> String -> Texture -> IO ()
-- | Change a texture parameter of a shader.
--
-- This function maps a shader texture variable to the texture of the
-- object being drawn, which cannot be known in advance.
--
-- The corresponding parameter in the shader must be a 2D texture
-- (sampler2D GLSL type).
setCurrentTextureParameter :: Shader -> String -> IO ()
-- | Bind the resource for rendering (activate it).
--
-- This function is not part of the graphics API, it mustn't be used when
-- drawing SFML entities. It must be used only if you mix sfShader with
-- OpenGL code.
bind :: SFBindable a => a -> IO ()
-- | Tell whether or not the system supports shaders.
--
-- This function should always be called before using the shader
-- features. If it returns False, then any attempt to use
-- Shader will fail.
isShaderAvailable :: IO Bool
instance SFBindable Shader
instance SFResource Shader
module SFML.Graphics.Shape
-- | Create a new shape.
createShape :: Ptr a -> Ptr b -> Ptr c -> IO Shape
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set the position of a transformable.
--
-- This function completely overwrites the previous position.
--
-- See move to apply an offset based on the previous position
-- instead.
--
-- The default position of a transformable object is (0, 0).
setPosition :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the orientation of a transformable.
--
-- This function completely overwrites the previous rotation.
--
-- See rotate to add an angle based on the previous rotation
-- instead.
--
-- The default rotation of a transformable SFTransformable object is 0.
setRotation :: SFTransformable a => a -> Float -> IO ()
-- | Set the scale factors of a transformable.
--
-- This function completely overwrites the previous scale.
--
-- See scale to add a factor based on the previous scale instead.
--
-- The default scale of a transformable SFTransformable object is (1, 1).
setScale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the local origin of a transformable.
--
-- The origin of an object defines the center point for all
-- transformations (position, scale, rotation).
--
-- The coordinates of this point must be relative to the top-left corner
-- of the object, and ignore all transformations (position, scale,
-- rotation).
--
-- The default origin of a transformable SFTransformable object is (0,
-- 0).
setOrigin :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the position of a transformable.
getPosition :: SFTransformable a => a -> IO Vec2f
-- | Get the orientation of a transformable.
getRotation :: SFTransformable a => a -> IO Float
-- | Get the current scale of a transformable
getScale :: SFTransformable a => a -> IO Vec2f
-- | Get the local origin of a transformable.
getOrigin :: SFTransformable a => a -> IO Vec2f
-- | Move a transformable by a given offset
--
-- This function adds to the current position of the object, unlike
-- setPosition which overwrites it.
move :: SFTransformable a => a -> Vec2f -> IO ()
-- | Rotate a transformable.
--
-- This function adds to the current rotation of the object, unlike
-- setRotation which overwrites it.
rotate :: SFTransformable a => a -> Float -> IO ()
-- | Scale a transformable.
--
-- This function multiplies the current scale of the object, unlike
-- setScale which overwrites it.
scale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the combined transform of a transformable.
getTransform :: SFTransformable a => a -> IO Transform
-- | Get the inverse of the combined transform of a transformable.
getInverseTransform :: SFTransformable a => a -> IO Transform
-- | Change the source texture of a Texturable.
--
-- The texture argument refers to a texture that must exist as long as
-- the texturable uses it. Indeed, the texturable doesn't store its own
-- copy of the texture, but rather keeps a pointer to the one that you
-- passed to this function.
--
-- If the source texture is destroyed and the texturable tries to use it,
-- the behaviour is undefined.
--
-- If resetRect is True, the TextureRect property of the
-- texturable is automatically adjusted to the size of the new texture.
-- If it is false, the texture rect is left unchanged.
setTexture :: SFTexturable a => a -> Texture -> Bool -> IO ()
-- | Set the sub-rectangle of the texture that a texturable will display.
--
-- The texture rect is useful when you don't want to display the whole
-- texture, but rather a part of it.
--
-- By default, the texture rect covers the entire texture.
setTextureRect :: SFTexturable a => a -> IntRect -> IO ()
-- | Get the source texture of a texturable.
--
-- If the texturable has no source texture, Nothing is returned.
--
-- The returned pointer is const, which means that you can't modify the
-- texture when you retrieve it with this function.
getTexture :: SFTexturable a => a -> IO (Maybe Texture)
-- | Get the sub-rectangle of the texture displayed by a texturable.
getTextureRect :: SFTexturable a => a -> IO IntRect
-- | Set the fill color of a shape.
--
-- This color is modulated (multiplied) with the shape's texture if any.
-- It can be used to colorize the shape, or change its global opacity.
--
-- You can use Transparent to make the inside of the shape
-- transparent, and have the outline alone.
--
-- By default, the shape's fill color is opaque white.
setFillColor :: SFShape a => a -> Color -> IO ()
-- | Set the outline color of a shape.
--
-- You can use Transparent to disable the outline.
--
-- By default, the shape's outline color is opaque white.
setOutlineColor :: SFShape a => a -> Color -> IO ()
-- | Set the thickness of a shape's outline.
--
-- This number cannot be negative. Using zero disables the outline.
--
-- By default, the outline thickness is 0.
setOutlineThickness :: SFShape a => a -> Float -> IO ()
-- | Get the fill color of a shape.
getFillColor :: SFShape a => a -> IO Color
-- | Get the outline color of a shape.
getOutlineColor :: SFShape a => a -> IO Color
-- | Get the outline thickness of a shape.
getOutlineThickness :: SFShape a => a -> IO Float
-- | Get the total number of points of a shape.
getPointCount :: SFShape a => a -> IO Int
-- | Get the ith point of a shape.
--
-- The result is undefined if index is out of the valid range.
getPoint :: SFShape a => a -> Int -> IO Vec2f
-- | Set the number of points of a resizable shape.
setPointCount :: SFShapeResizable a => a -> Int -> IO ()
-- | Get the local bounding rectangle of a boundable.
--
-- The returned rectangle is in local coordinates, which means that it
-- ignores the transformations (translation, rotation, scale, ...) that
-- are applied to the entity. In other words, this function returns the
-- bounds of the entity in the entity's coordinate system.
getLocalBounds :: SFBounded a => a -> IO FloatRect
-- | Get the global bounding rectangle of a shape.
--
-- The returned rectangle is in global coordinates, which means that it
-- takes in account the transformations (translation, rotation, scale,
-- ...) that are applied to the entity. In other words, this function
-- returns the bounds of the sprite in the global 2D world's coordinate
-- system.
getGlobalBounds :: SFBounded a => a -> IO FloatRect
-- | Recompute the internal geometry of a shape.
--
-- This function must be called by specialized shape objects everytime
-- their points change (ie. the result of either the getPointCount or
-- getPoint callbacks is different).
updateShape :: Shape -> IO ()
instance SFBounded Shape
instance SFShape Shape
instance SFTexturable Shape
instance SFTransformable Shape
instance SFResource Shape
module SFML.Graphics.Text
-- | Text styles.
data TextStyle
-- | Regular characters, no style
TextRegular :: TextStyle
-- | Characters are bold
TextBold :: TextStyle
-- | Characters are in italic
TextItalic :: TextStyle
-- | Characters are underlined
TextUnderlined :: TextStyle
-- | Strike through characters
TextStrikeThrough :: TextStyle
-- | Create a new text.
createText :: IO (Either SFException Text)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set the string of a text (from an ANSI string).
--
-- A text's string is empty by default.
setTextString :: Text -> String -> IO ()
-- | Set the string of a text (from a unicode string).
setTextStringU :: Text -> String -> IO ()
-- | Set the font of a text.
--
-- The font argument refers to a texture that must exist as long as the
-- text uses it. Indeed, the text doesn't store its own copy of the font,
-- but rather keeps a pointer to the one that you passed to this
-- function. If the font is destroyed and the text tries to use it, the
-- behaviour is undefined.
setTextFont :: Text -> Font -> IO ()
-- | Set the character size of a text.
--
-- The default size is 30.
setTextCharacterSize :: Text -> Int -> IO ()
-- | Set the style of a text.
--
-- You can pass a combination of one or more styles, for example
-- [TextBold, sfTextItalic].
--
-- The default style is TextRegular.
setTextStyle :: Text -> [TextStyle] -> IO ()
-- | Set the global color of a text.
--
-- By default, the text's color is opaque white.
setTextColor :: Text -> Color -> IO ()
-- | Get the string of a text as an ANSI string.
getTextString :: Text -> IO String
-- | Get the string of a text as a UTF-32 string.
getTextUnicodeString :: Text -> IO String
-- | Get the font used by a text.
--
-- If the text has no font attached, Nothing is returned.
--
-- The returned pointer is const, which means that you can't modify the
-- font when you retrieve it with this function.
getTextFont :: Text -> IO (Maybe Font)
-- | Get the size of the characters of a text.
getTextCharacterSize :: Text -> IO Int
-- | Get the style of a text
getTextStyle :: Text -> IO TextStyle
-- | Get the global color of a text.
getTextColor :: Text -> IO Color
-- | Return the position of the ith character in a text.
--
-- This function computes the visual position of a character from its
-- index in the string. The returned position is in global coordinates
-- (translation, rotation, scale and origin are applied).
--
-- If the index is out of range, the position of the end of the string is
-- returned.
findTextCharacterPos :: Text -> Int -> IO Vec2f
-- | Get the local bounding rectangle of a boundable.
--
-- The returned rectangle is in local coordinates, which means that it
-- ignores the transformations (translation, rotation, scale, ...) that
-- are applied to the entity. In other words, this function returns the
-- bounds of the entity in the entity's coordinate system.
getLocalBounds :: SFBounded a => a -> IO FloatRect
-- | Get the global bounding rectangle of a shape.
--
-- The returned rectangle is in global coordinates, which means that it
-- takes in account the transformations (translation, rotation, scale,
-- ...) that are applied to the entity. In other words, this function
-- returns the bounds of the sprite in the global 2D world's coordinate
-- system.
getGlobalBounds :: SFBounded a => a -> IO FloatRect
instance Eq TextStyle
instance Bounded TextStyle
instance Show TextStyle
instance SFBounded Text
instance SFTransformable Text
instance SFResource Text
instance SFCopyable Text
instance Enum TextStyle
module SFML.Graphics.Vertex
-- | Define a point with color and texture coordinates.
data Vertex
Vertex :: Vec2f -> Color -> Vec2f -> Vertex
position :: Vertex -> Vec2f
color :: Vertex -> Color
texCoords :: Vertex -> Vec2f
instance Show Vertex
instance Storable Vertex
module SFML.Graphics.VertexArray
-- | Create a new vertex array.
createVA :: IO VertexArray
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Return the vertex count of a vertex array.
getVertexCount :: VertexArray -> IO Int
-- | Return the ith vertex.
getVertex :: VertexArray -> Int -> IO (Ptr Vertex)
-- | Clear a vertex array.
--
-- This function removes all the vertices from the array. It doesn't
-- deallocate the corresponding memory, so that adding new vertices after
-- clearing doesn't involve reallocating all the memory.
clearVA :: VertexArray -> IO ()
-- | Resize the vertex array.
--
-- If vertex count is greater than the current size, the previous
-- vertices are kept and new (default-constructed) vertices are added.
--
-- If vertex count is less than the current size, existing vertices are
-- removed from the array.
resizeVA :: VertexArray -> Int -> IO ()
-- | Add a vertex to a vertex array array.
appendVA :: VertexArray -> Vertex -> IO ()
-- | Set the type of primitives of a vertex array.
--
-- This function defines how the vertices must be interpreted when it's
-- time to draw them:
--
--
-- - As points
-- - As lines
-- - As triangles
-- - As quads
--
--
-- The default primitive type is sfPoints.
setPrimitiveType :: VertexArray -> PrimitiveType -> IO ()
-- | Get the type of primitives drawn by a vertex array.
getPrimitiveType :: VertexArray -> IO PrimitiveType
-- | Compute the bounding rectangle of a vertex array.
--
-- This function returns the axis-aligned rectangle that contains all the
-- vertices of the array.
getVABounds :: VertexArray -> IO FloatRect
instance SFResource VertexArray
instance SFCopyable VertexArray
module SFML.Graphics.CircleShape
-- | Create a new circle shape.
createCircleShape :: IO (Either SFException CircleShape)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set the position of a transformable.
--
-- This function completely overwrites the previous position.
--
-- See move to apply an offset based on the previous position
-- instead.
--
-- The default position of a transformable object is (0, 0).
setPosition :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the orientation of a transformable.
--
-- This function completely overwrites the previous rotation.
--
-- See rotate to add an angle based on the previous rotation
-- instead.
--
-- The default rotation of a transformable SFTransformable object is 0.
setRotation :: SFTransformable a => a -> Float -> IO ()
-- | Set the scale factors of a transformable.
--
-- This function completely overwrites the previous scale.
--
-- See scale to add a factor based on the previous scale instead.
--
-- The default scale of a transformable SFTransformable object is (1, 1).
setScale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the local origin of a transformable.
--
-- The origin of an object defines the center point for all
-- transformations (position, scale, rotation).
--
-- The coordinates of this point must be relative to the top-left corner
-- of the object, and ignore all transformations (position, scale,
-- rotation).
--
-- The default origin of a transformable SFTransformable object is (0,
-- 0).
setOrigin :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the position of a transformable.
getPosition :: SFTransformable a => a -> IO Vec2f
-- | Get the orientation of a transformable.
getRotation :: SFTransformable a => a -> IO Float
-- | Get the current scale of a transformable
getScale :: SFTransformable a => a -> IO Vec2f
-- | Get the local origin of a transformable.
getOrigin :: SFTransformable a => a -> IO Vec2f
-- | Move a transformable by a given offset
--
-- This function adds to the current position of the object, unlike
-- setPosition which overwrites it.
move :: SFTransformable a => a -> Vec2f -> IO ()
-- | Rotate a transformable.
--
-- This function adds to the current rotation of the object, unlike
-- setRotation which overwrites it.
rotate :: SFTransformable a => a -> Float -> IO ()
-- | Scale a transformable.
--
-- This function multiplies the current scale of the object, unlike
-- setScale which overwrites it.
scale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the combined transform of a transformable.
getTransform :: SFTransformable a => a -> IO Transform
-- | Get the inverse of the combined transform of a transformable.
getInverseTransform :: SFTransformable a => a -> IO Transform
-- | Change the source texture of a Texturable.
--
-- The texture argument refers to a texture that must exist as long as
-- the texturable uses it. Indeed, the texturable doesn't store its own
-- copy of the texture, but rather keeps a pointer to the one that you
-- passed to this function.
--
-- If the source texture is destroyed and the texturable tries to use it,
-- the behaviour is undefined.
--
-- If resetRect is True, the TextureRect property of the
-- texturable is automatically adjusted to the size of the new texture.
-- If it is false, the texture rect is left unchanged.
setTexture :: SFTexturable a => a -> Texture -> Bool -> IO ()
-- | Set the sub-rectangle of the texture that a texturable will display.
--
-- The texture rect is useful when you don't want to display the whole
-- texture, but rather a part of it.
--
-- By default, the texture rect covers the entire texture.
setTextureRect :: SFTexturable a => a -> IntRect -> IO ()
-- | Get the source texture of a texturable.
--
-- If the texturable has no source texture, Nothing is returned.
--
-- The returned pointer is const, which means that you can't modify the
-- texture when you retrieve it with this function.
getTexture :: SFTexturable a => a -> IO (Maybe Texture)
-- | Get the sub-rectangle of the texture displayed by a texturable.
getTextureRect :: SFTexturable a => a -> IO IntRect
-- | Set the fill color of a shape.
--
-- This color is modulated (multiplied) with the shape's texture if any.
-- It can be used to colorize the shape, or change its global opacity.
--
-- You can use Transparent to make the inside of the shape
-- transparent, and have the outline alone.
--
-- By default, the shape's fill color is opaque white.
setFillColor :: SFShape a => a -> Color -> IO ()
-- | Set the outline color of a shape.
--
-- You can use Transparent to disable the outline.
--
-- By default, the shape's outline color is opaque white.
setOutlineColor :: SFShape a => a -> Color -> IO ()
-- | Set the thickness of a shape's outline.
--
-- This number cannot be negative. Using zero disables the outline.
--
-- By default, the outline thickness is 0.
setOutlineThickness :: SFShape a => a -> Float -> IO ()
-- | Get the fill color of a shape.
getFillColor :: SFShape a => a -> IO Color
-- | Get the outline color of a shape.
getOutlineColor :: SFShape a => a -> IO Color
-- | Get the outline thickness of a shape.
getOutlineThickness :: SFShape a => a -> IO Float
-- | Get the total number of points of a shape.
getPointCount :: SFShape a => a -> IO Int
-- | Get the ith point of a shape.
--
-- The result is undefined if index is out of the valid range.
getPoint :: SFShape a => a -> Int -> IO Vec2f
-- | Set the radius of a circle.
setRadius :: CircleShape -> Float -> IO ()
-- | Get the radius of a circle.
getRadius :: CircleShape -> IO Float
-- | Set the number of points of a resizable shape.
setPointCount :: SFShapeResizable a => a -> Int -> IO ()
-- | Get the local bounding rectangle of a boundable.
--
-- The returned rectangle is in local coordinates, which means that it
-- ignores the transformations (translation, rotation, scale, ...) that
-- are applied to the entity. In other words, this function returns the
-- bounds of the entity in the entity's coordinate system.
getLocalBounds :: SFBounded a => a -> IO FloatRect
-- | Get the global bounding rectangle of a shape.
--
-- The returned rectangle is in global coordinates, which means that it
-- takes in account the transformations (translation, rotation, scale,
-- ...) that are applied to the entity. In other words, this function
-- returns the bounds of the sprite in the global 2D world's coordinate
-- system.
getGlobalBounds :: SFBounded a => a -> IO FloatRect
instance SFBounded CircleShape
instance SFShapeResizable CircleShape
instance SFShape CircleShape
instance SFTexturable CircleShape
instance SFTransformable CircleShape
instance SFResource CircleShape
instance SFCopyable CircleShape
module SFML.Graphics.BlendMode
-- | Enumeration of the blending factors
data BlendFactor
-- | (0, 0, 0, 0)
BlendFactorZero :: BlendFactor
-- | (1, 1, 1, 1)
BlendFactorOne :: BlendFactor
-- | (src.r, src.g, src.b, src.a)
BlendFactorSrcColor :: BlendFactor
-- | (1, 1, 1, 1) - (src.r, src.g, src.b, src.a)
BlendFactorOneMinusSrcColor :: BlendFactor
-- | (dst.r, dst.g, dst.b, dst.a)
BlendFactorDstColor :: BlendFactor
-- | (1, 1, 1, 1) - (dst.r, dst.g, dst.b, dst.a)
BlendFactorOneMinusDstColor :: BlendFactor
-- | (src.a, src.a, src.a, src.a)
BlendFactorSrcAlpha :: BlendFactor
-- | (1, 1, 1, 1) - (src.a, src.a, src.a, src.a)
BlendFactorOneMinusSrcAlpha :: BlendFactor
-- | (dst.a, dst.a, dst.a, dst.a)
BlendFactorDstAlpha :: BlendFactor
-- | (1, 1, 1, 1) - (dst.a, dst.a, dst.a, dst.a)
BlendFactorOneMinusDstAlpha :: BlendFactor
-- | Enumeration of the blending equations
data BlendEquation
-- | Pixel = Src * SrcFactor + Dst * DstFactor
BlendEquationAdd :: BlendEquation
-- | Pixel = Src * SrcFactor - Dst * DstFactor
BlendEquationSubtract :: BlendEquation
-- | Available blending modes for drawing.
data BlendMode
BlendMode :: BlendFactor -> BlendFactor -> BlendEquation -> BlendFactor -> BlendFactor -> BlendEquation -> BlendMode
-- | Source blending factor for the color channels
colorSrcFactor :: BlendMode -> BlendFactor
-- | Destination blending factor for the color channels
colorDstFactor :: BlendMode -> BlendFactor
-- | Blending equation for the color channels
colorEquation :: BlendMode -> BlendEquation
-- | Source blending factor for the alpha channel
alphaSrcFactor :: BlendMode -> BlendFactor
-- | Destination blending factor for the alpha channel
alphaDstFactor :: BlendMode -> BlendFactor
-- | Blending equation for the alpha channel
alphaEquation :: BlendMode -> BlendEquation
blendAlpha :: BlendMode
blendAdd :: BlendMode
blendMultiply :: BlendMode
blendNone :: BlendMode
instance Eq BlendFactor
instance Enum BlendFactor
instance Bounded BlendFactor
instance Show BlendFactor
instance Eq BlendEquation
instance Enum BlendEquation
instance Bounded BlendEquation
instance Show BlendEquation
instance Eq BlendMode
instance Show BlendMode
instance Storable BlendMode
instance Storable BlendEquation
instance Storable BlendFactor
module SFML.Graphics.RenderStates
-- | Define the states used for drawing to a RenderTarget.
data RenderStates
RenderStates :: BlendMode -> Transform -> Texture -> Shader -> RenderStates
blendMode :: RenderStates -> BlendMode
transform :: RenderStates -> Transform
texture :: RenderStates -> Texture
shader :: RenderStates -> Shader
-- | Default render states, defined as
--
--
-- renderStates = RenderStates blendAlpha idTransform (Texture nullPtr) (Shader nullPtr)
--
--
-- This constant tries to mimic the C++ RenderStates default constructor
-- to ease the construction of render states. For example, instead of
-- typing
--
--
-- states = RenderStates blendAlpha idTransform tex (Shader nullptr)
--
--
-- Now we can simply type
--
--
-- states = renderStates { texture = tex }
--
renderStates :: RenderStates
instance Storable RenderStates
module SFML.Graphics.SFRenderTarget
class SFRenderTarget a
drawSprite :: SFRenderTarget a => a -> Sprite -> Maybe RenderStates -> IO ()
drawText :: SFRenderTarget a => a -> Text -> Maybe RenderStates -> IO ()
drawShape :: SFRenderTarget a => a -> Shape -> Maybe RenderStates -> IO ()
drawCircle :: SFRenderTarget a => a -> CircleShape -> Maybe RenderStates -> IO ()
drawConvexShape :: SFRenderTarget a => a -> ConvexShape -> Maybe RenderStates -> IO ()
drawRectangle :: SFRenderTarget a => a -> RectangleShape -> Maybe RenderStates -> IO ()
drawVertexArray :: SFRenderTarget a => a -> VertexArray -> Maybe RenderStates -> IO ()
drawPrimitives :: SFRenderTarget a => a -> [Vertex] -> PrimitiveType -> Maybe RenderStates -> IO ()
drawPrimitives' :: SFRenderTarget a => a -> Ptr Vertex -> Int -> PrimitiveType -> Maybe RenderStates -> IO ()
pushGLStates :: SFRenderTarget a => a -> IO ()
popGLStates :: SFRenderTarget a => a -> IO ()
resetGLStates :: SFRenderTarget a => a -> IO ()
module SFML.Graphics.RenderTexture
-- | Construct a new render texture.
createRenderTexture :: Int -> Int -> Bool -> IO (Either SFException RenderTexture)
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Get the size of the rendering region of a render texture.
getTextureSize :: RenderTexture -> IO Vec2u
-- | Activate or deactivate a render texture as the current target for
-- rendering.
setActive :: RenderTexture -> Bool -> IO Bool
-- | Update the target's contents.
display :: SFDisplayable a => a -> IO ()
-- | Clear the rendertexture with the given color.
clear :: RenderTexture -> Color -> IO ()
-- | Change the target's current active view.
setView :: SFViewable a => a -> View -> IO ()
-- | Get the target's current active view.
getView :: SFViewable a => a -> IO View
-- | Get the target's default view.
getDefaultView :: SFViewable a => a -> IO View
-- | Get the viewport of a view applied to this target, expressed in pixels
-- in the current target.
getViewport :: SFViewable a => a -> View -> IO IntRect
-- | Convert a point to world coordinates
--
-- This function finds the 2D position that matches the given pixel of
-- the coord space. In other words, it does the inverse of what the
-- graphics card does, to find the initial position of a rendered pixel.
--
-- Initially, both coordinate systems (world units and target pixels)
-- match perfectly. But if you define a custom view or resize your coord
-- space, this assertion is not true anymore, ie. a point located at (10,
-- 50) in your coord space may map to the point (150, 75) in your 2D
-- world -- if the view is translated by (140, 25).
--
-- This version uses a custom view for calculations, see the other
-- overload of the function if you want to use the current view of the
-- render-texture.
mapPixelToCoords :: SFCoordSpace a => a -> Vec2i -> Maybe View -> IO Vec2f
-- | Draw a sprite to the render-target.
drawSprite :: SFRenderTarget a => a -> Sprite -> Maybe RenderStates -> IO ()
-- | Draw text to the render-target.
drawText :: SFRenderTarget a => a -> Text -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawShape :: SFRenderTarget a => a -> Shape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawCircle :: SFRenderTarget a => a -> CircleShape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawConvexShape :: SFRenderTarget a => a -> ConvexShape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawRectangle :: SFRenderTarget a => a -> RectangleShape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawVertexArray :: SFRenderTarget a => a -> VertexArray -> Maybe RenderStates -> IO ()
-- | Draw primitives defined by an array of vertices to a render texture.
drawPrimitives :: SFRenderTarget a => a -> [Vertex] -> PrimitiveType -> Maybe RenderStates -> IO ()
drawPrimitives' :: SFRenderTarget a => a -> Ptr Vertex -> Int -> PrimitiveType -> Maybe RenderStates -> IO ()
-- | Save the current OpenGL render states and matrices.
--
-- This function can be used when you mix SFML drawing and direct OpenGL
-- rendering. Combined with popGLStates, it ensures that:
--
--
-- - SFML's internal states are not messed up by your OpenGL code
-- - Your OpenGL states are not modified by a call to a SFML
-- function
--
--
-- Note that this function is quite expensive: it saves all the possible
-- OpenGL states and matrices, even the ones you don't care about.
-- Therefore it should be used wisely. It is provided for convenience,
-- but the best results will be achieved if you handle OpenGL states
-- yourself (because you know which states have really changed, and need
-- to be saved and restored). Take a look at the resetGLStates function
-- if you do so.
pushGLStates :: SFRenderTarget a => a -> IO ()
-- | Restore the previously saved OpenGL render states and matrices.
--
-- See the description of pushGLStates to get a detailed description of
-- these functions.
popGLStates :: SFRenderTarget a => a -> IO ()
-- | Reset the internal OpenGL states so that the target is ready for
-- drawing
--
-- This function can be used when you mix SFML drawing and direct OpenGL
-- rendering, if you choose not to use pushGLStates or
-- popGLStates. It makes sure that all OpenGL states needed by
-- SFML are set, so that subsequent draw calls will work as expected.
resetGLStates :: SFRenderTarget a => a -> IO ()
-- | Get the target texture of a render texture.
getRenderTexture :: RenderTexture -> IO Texture
-- | Enable or disable the smooth filter on a texture.
setSmooth :: SFSmoothTexture a => a -> Bool -> IO ()
-- | Tell whether the smooth filter is enabled or not for a texture.
isSmooth :: SFSmoothTexture a => a -> IO Bool
instance SFSmoothTexture RenderTexture
instance SFRenderTarget RenderTexture
instance SFCoordSpace RenderTexture
instance SFViewable RenderTexture
instance SFDisplayable RenderTexture
instance SFResource RenderTexture
module SFML.Graphics.RenderWindow
-- | Construct a new render window.
createRenderWindow :: VideoMode -> String -> [WindowStyle] -> Maybe ContextSettings -> IO RenderWindow
-- | Construct a render window from an existing control.
renderWindowFromHandle :: WindowHandle -> Maybe ContextSettings -> IO RenderWindow
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Close the window.
--
-- After calling this function, the window object remains valid; you must
-- call destroy to actually delete it.
close :: SFWindow a => a -> IO ()
-- | Tell whether or not a window is opened
--
-- This function returns whether or not the window exists.
--
-- Note that a hidden window (setWindowVisible False ) will return
-- True.
isWindowOpen :: SFWindow a => a -> IO Bool
-- | Get the settings of the OpenGL context of a window.
--
-- Note that these settings may be different from what was passed to the
-- window create function, if one or more settings were not supported. In
-- this case, SFML chose the closest match.
getWindowSettings :: SFWindow a => a -> IO ContextSettings
-- | Pop the event on top of events stack, if any, and return it.
--
-- This function is not blocking: if there's no pending event then it
-- will return false and leave a event unmodified. Note that more than
-- one event may be present in the events stack, thus you should always
-- call this function in a loop to make sure that you process every
-- pending event.
pollEvent :: SFWindow a => a -> IO (Maybe SFEvent)
-- | Wait for an event and return it.
--
-- This function is blocking: if there's no pending event then it will
-- wait until an event is received.
--
-- After this function returns (and no error occured), the event object
-- is always valid and filled properly.
--
-- This function is typically used when you have a thread that is
-- dedicated to events handling: you want to make this thread sleep as
-- long as no new event is received.
waitEvent :: SFWindow a => a -> IO (Maybe SFEvent)
-- | Get the position of a window.
getWindowPosition :: SFWindow a => a -> IO Vec2i
-- | Change the position of a window on screen.
--
-- This function only works for top-level windows (i.e. it will be
-- ignored for windows created from the handle of a child
-- window/control).
setWindowPosition :: SFWindow a => a -> Vec2i -> IO ()
-- | Get the size of the rendering region of a window.
--
-- The size doesn't include the titlebar and borders of the window.
getWindowSize :: SFWindow a => a -> IO Vec2u
-- | Change the size of the rendering region of a window.
setWindowSize :: SFWindow a => a -> Vec2u -> IO ()
-- | Change the title of a window.
setWindowTitle :: SFWindow a => a -> String -> IO ()
-- | Change a window's icon.
--
-- Pixels must be an array of width x height pixels in 32-bits RGBA
-- format.
setWindowIcon :: SFWindow a => a -> Int -> Int -> Ptr b -> IO ()
-- | Show or hide a window.
setWindowVisible :: SFWindow a => a -> Bool -> IO ()
-- | Show or hide the mouse cursor.
setMouseVisible :: SFWindow a => a -> Bool -> IO ()
-- | Enable or disable vertical synchronization. Activating vertical
-- synchronization will limit the number of frames displayed to the
-- refresh rate of the monitor.
--
-- This can avoid some visual artifacts, and limit the framerate to a
-- good value (but not constant across different computers).
setVSync :: SFWindow a => a -> Bool -> IO ()
-- | Enable or disable automatic key-repeat.
--
-- If key repeat is enabled, you will receive repeated KeyPress events
-- while keeping a key pressed. If it is disabled, you will only get a
-- single event when the key is pressed.
--
-- Key repeat is enabled by default.
setKeyRepeat :: SFWindow a => a -> Bool -> IO ()
-- | Activate or deactivate a window as the current target for OpenGL
-- rendering.
--
-- A window is active only on the current thread, if you want to make it
-- active on another thread you have to deactivate it on the previous
-- thread first if it was active.
--
-- Only one window can be active on a thread at a time, thus the window
-- previously active (if any) automatically gets deactivated.
setWindowActive :: SFWindow a => a -> Bool -> IO ()
-- | Request the current window to be made the active foreground window.
--
-- At any given time, only one window may have the input focus to receive
-- input events such as keystrokes or mouse events. If a window requests
-- focus, it only hints to the operating system, that it would like to be
-- focused. The operating system is free to deny the request. This is not
-- to be confused with setWindowActive.
requestFocus :: SFWindow a => a -> IO ()
-- | Check whether the render window has the input focus.
--
-- At any given time, only one window may have the input focus to receive
-- input events such as keystrokes or most mouse events.
hasFocus :: SFWindow a => a -> IO Bool
-- | Update the target's contents.
display :: SFDisplayable a => a -> IO ()
-- | Limit the framerate to a maximum fixed frequency.
--
-- If a limit is set, the window will use a small delay after each call
-- to display to ensure that the current frame lasted long enough
-- to match the framerate limit.
setFramerateLimit :: SFWindow a => a -> Int -> IO ()
-- | Change the joystick threshold.
--
-- The joystick threshold is the value below which no JoyMoved event will
-- be generated.
setJoystickThreshold :: SFWindow a => a -> Float -> IO ()
-- | Get the OS-specific handle of the window.
--
-- The type of the returned handle is WindowHandle, which is a
-- typedef to the handle type defined by the OS.
--
-- You shouldn't need to use this function, unless you have very specific
-- stuff to implement that SFML doesn't support, or implement a temporary
-- workaround until a bug is fixed.
getSystemHandle :: SFWindow a => a -> IO WindowHandle
-- | Clear a render window with the given color.
clearRenderWindow :: RenderWindow -> Color -> IO ()
-- | Change the target's current active view.
setView :: SFViewable a => a -> View -> IO ()
-- | Get the target's current active view.
getView :: SFViewable a => a -> IO View
-- | Get the target's default view.
getDefaultView :: SFViewable a => a -> IO View
-- | Get the viewport of a view applied to this target, expressed in pixels
-- in the current target.
getViewport :: SFViewable a => a -> View -> IO IntRect
-- | Convert a point to world coordinates
--
-- This function finds the 2D position that matches the given pixel of
-- the coord space. In other words, it does the inverse of what the
-- graphics card does, to find the initial position of a rendered pixel.
--
-- Initially, both coordinate systems (world units and target pixels)
-- match perfectly. But if you define a custom view or resize your coord
-- space, this assertion is not true anymore, ie. a point located at (10,
-- 50) in your coord space may map to the point (150, 75) in your 2D
-- world -- if the view is translated by (140, 25).
--
-- This version uses a custom view for calculations, see the other
-- overload of the function if you want to use the current view of the
-- render-texture.
mapPixelToCoords :: SFCoordSpace a => a -> Vec2i -> Maybe View -> IO Vec2f
-- | Draw a sprite to the render-target.
drawSprite :: SFRenderTarget a => a -> Sprite -> Maybe RenderStates -> IO ()
-- | Draw text to the render-target.
drawText :: SFRenderTarget a => a -> Text -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawShape :: SFRenderTarget a => a -> Shape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawCircle :: SFRenderTarget a => a -> CircleShape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawConvexShape :: SFRenderTarget a => a -> ConvexShape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawRectangle :: SFRenderTarget a => a -> RectangleShape -> Maybe RenderStates -> IO ()
-- | Draw a sprite to the render-target.
drawVertexArray :: SFRenderTarget a => a -> VertexArray -> Maybe RenderStates -> IO ()
-- | Draw primitives defined by an array of vertices to a render texture.
drawPrimitives :: SFRenderTarget a => a -> [Vertex] -> PrimitiveType -> Maybe RenderStates -> IO ()
drawPrimitives' :: SFRenderTarget a => a -> Ptr Vertex -> Int -> PrimitiveType -> Maybe RenderStates -> IO ()
-- | Save the current OpenGL render states and matrices.
--
-- This function can be used when you mix SFML drawing and direct OpenGL
-- rendering. Combined with popGLStates, it ensures that:
--
--
-- - SFML's internal states are not messed up by your OpenGL code
-- - Your OpenGL states are not modified by a call to a SFML
-- function
--
--
-- Note that this function is quite expensive: it saves all the possible
-- OpenGL states and matrices, even the ones you don't care about.
-- Therefore it should be used wisely. It is provided for convenience,
-- but the best results will be achieved if you handle OpenGL states
-- yourself (because you know which states have really changed, and need
-- to be saved and restored). Take a look at the resetGLStates function
-- if you do so.
pushGLStates :: SFRenderTarget a => a -> IO ()
-- | Restore the previously saved OpenGL render states and matrices.
--
-- See the description of pushGLStates to get a detailed description of
-- these functions.
popGLStates :: SFRenderTarget a => a -> IO ()
-- | Reset the internal OpenGL states so that the target is ready for
-- drawing
--
-- This function can be used when you mix SFML drawing and direct OpenGL
-- rendering, if you choose not to use pushGLStates or
-- popGLStates. It makes sure that all OpenGL states needed by
-- SFML are set, so that subsequent draw calls will work as expected.
resetGLStates :: SFRenderTarget a => a -> IO ()
-- | Copy the current contents of a render window to an image.
--
-- This is a slow operation, whose main purpose is to make screenshots of
-- the application. If you want to update an image with the contents of
-- the window and then use it for drawing, you should rather use a
-- Texture and its update(sfWindow*) function.
--
-- You can also draw things directly to a texture with the sfRenderWindow
-- class.
captureRenderWindow :: RenderWindow -> IO Image
-- | Get the current position of the mouse
--
-- This function returns the current position of the mouse cursor
-- relative to the given window, or desktop if Nothing is passed.
getMousePosition :: SFWindow a => Maybe a -> IO Vec2i
-- | Set the current position of the mouse
--
-- This function sets the current position of the mouse cursor relative
-- to the given window, or desktop if Nothing is passed.
setMousePosition :: SFWindow a => Vec2i -> Maybe a -> IO ()
instance SFRenderTarget RenderWindow
instance SFCoordSpace RenderWindow
instance SFViewable RenderWindow
instance SFWindow RenderWindow
instance SFDisplayable RenderWindow
instance SFResource RenderWindow
module SFML.Graphics.SFDrawable
class SFDrawable a
draw :: (SFDrawable a, SFRenderTarget t) => t -> a -> Maybe RenderStates -> IO ()
instance SFDrawable VertexArray
instance SFDrawable ConvexShape
instance SFDrawable CircleShape
instance SFDrawable Shape
instance SFDrawable Text
instance SFDrawable Sprite
module SFML.Graphics.Sprite
-- | Create a new sprite.
createSprite :: IO (Either SFException Sprite)
-- | Copy the given SFML resource.
copy :: SFCopyable a => a -> IO a
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set the position of a transformable.
--
-- This function completely overwrites the previous position.
--
-- See move to apply an offset based on the previous position
-- instead.
--
-- The default position of a transformable object is (0, 0).
setPosition :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the orientation of a transformable.
--
-- This function completely overwrites the previous rotation.
--
-- See rotate to add an angle based on the previous rotation
-- instead.
--
-- The default rotation of a transformable SFTransformable object is 0.
setRotation :: SFTransformable a => a -> Float -> IO ()
-- | Set the scale factors of a transformable.
--
-- This function completely overwrites the previous scale.
--
-- See scale to add a factor based on the previous scale instead.
--
-- The default scale of a transformable SFTransformable object is (1, 1).
setScale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Set the local origin of a transformable.
--
-- The origin of an object defines the center point for all
-- transformations (position, scale, rotation).
--
-- The coordinates of this point must be relative to the top-left corner
-- of the object, and ignore all transformations (position, scale,
-- rotation).
--
-- The default origin of a transformable SFTransformable object is (0,
-- 0).
setOrigin :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the position of a transformable.
getPosition :: SFTransformable a => a -> IO Vec2f
-- | Get the orientation of a transformable.
getRotation :: SFTransformable a => a -> IO Float
-- | Get the current scale of a transformable
getScale :: SFTransformable a => a -> IO Vec2f
-- | Get the local origin of a transformable.
getOrigin :: SFTransformable a => a -> IO Vec2f
-- | Move a transformable by a given offset
--
-- This function adds to the current position of the object, unlike
-- setPosition which overwrites it.
move :: SFTransformable a => a -> Vec2f -> IO ()
-- | Rotate a transformable.
--
-- This function adds to the current rotation of the object, unlike
-- setRotation which overwrites it.
rotate :: SFTransformable a => a -> Float -> IO ()
-- | Scale a transformable.
--
-- This function multiplies the current scale of the object, unlike
-- setScale which overwrites it.
scale :: SFTransformable a => a -> Vec2f -> IO ()
-- | Get the combined transform of a transformable.
getTransform :: SFTransformable a => a -> IO Transform
-- | Get the inverse of the combined transform of a transformable.
getInverseTransform :: SFTransformable a => a -> IO Transform
-- | Set the global color of a sprite.
--
-- This color is modulated (multiplied) with the sprite's texture. It can
-- be used to colorize the sprite, or change its global opacity. By
-- default, the sprite's color is opaque white.
setColor :: Sprite -> Color -> IO ()
-- | Get the global color of a sprite.
getColor :: Sprite -> IO Color
-- | Change the source texture of a Texturable.
--
-- The texture argument refers to a texture that must exist as long as
-- the texturable uses it. Indeed, the texturable doesn't store its own
-- copy of the texture, but rather keeps a pointer to the one that you
-- passed to this function.
--
-- If the source texture is destroyed and the texturable tries to use it,
-- the behaviour is undefined.
--
-- If resetRect is True, the TextureRect property of the
-- texturable is automatically adjusted to the size of the new texture.
-- If it is false, the texture rect is left unchanged.
setTexture :: SFTexturable a => a -> Texture -> Bool -> IO ()
-- | Set the sub-rectangle of the texture that a texturable will display.
--
-- The texture rect is useful when you don't want to display the whole
-- texture, but rather a part of it.
--
-- By default, the texture rect covers the entire texture.
setTextureRect :: SFTexturable a => a -> IntRect -> IO ()
-- | Get the source texture of a texturable.
--
-- If the texturable has no source texture, Nothing is returned.
--
-- The returned pointer is const, which means that you can't modify the
-- texture when you retrieve it with this function.
getTexture :: SFTexturable a => a -> IO (Maybe Texture)
-- | Get the sub-rectangle of the texture displayed by a texturable.
getTextureRect :: SFTexturable a => a -> IO IntRect
-- | Get the local bounding rectangle of a boundable.
--
-- The returned rectangle is in local coordinates, which means that it
-- ignores the transformations (translation, rotation, scale, ...) that
-- are applied to the entity. In other words, this function returns the
-- bounds of the entity in the entity's coordinate system.
getLocalBounds :: SFBounded a => a -> IO FloatRect
-- | Get the global bounding rectangle of a shape.
--
-- The returned rectangle is in global coordinates, which means that it
-- takes in account the transformations (translation, rotation, scale,
-- ...) that are applied to the entity. In other words, this function
-- returns the bounds of the sprite in the global 2D world's coordinate
-- system.
getGlobalBounds :: SFBounded a => a -> IO FloatRect
instance SFBounded Sprite
instance SFTexturable Sprite
instance SFTransformable Sprite
instance SFResource Sprite
instance SFCopyable Sprite
module SFML.Graphics
module SFML.Audio.Types
newtype Music
Music :: (Ptr Music) -> Music
newtype Sound
Sound :: (Ptr Sound) -> Sound
newtype SoundBuffer
SoundBuffer :: (Ptr SoundBuffer) -> SoundBuffer
newtype SoundBufferRecorder
SoundBufferRecorder :: (Ptr SoundBufferRecorder) -> SoundBufferRecorder
newtype SoundRecorder
SoundRecorder :: (Ptr SoundRecorder) -> SoundRecorder
newtype SoundStream
SoundStream :: (Ptr SoundStream) -> SoundStream
module SFML.Audio.SoundStatus
-- | Enumeration of statuses for sounds and musics
data SoundStatus
-- | Sound or music is not playing
Stopped :: SoundStatus
-- | Sound or music is paused
Paused :: SoundStatus
-- | Sound or music is playing
Playing :: SoundStatus
instance Eq SoundStatus
instance Enum SoundStatus
instance Bounded SoundStatus
instance Show SoundStatus
module SFML.Audio.SFSoundRecorder
class SFSoundRecorder a
startRecording :: SFSoundRecorder a => a -> Int -> IO Bool
stopRecording :: SFSoundRecorder a => a -> IO ()
module SFML.Audio.SFSound
class SFSound a
play :: SFSound a => a -> IO ()
pause :: SFSound a => a -> IO ()
stop :: SFSound a => a -> IO ()
getAttenuation :: SFSound a => a -> IO Float
getLoop :: SFSound a => a -> IO Bool
getMinDistance :: SFSound a => a -> IO Float
getPitch :: SFSound a => a -> IO Float
getPlayingOffset :: SFSound a => a -> IO Time
getPosition :: SFSound a => a -> IO Vec3f
getStatus :: SFSound a => a -> IO SoundStatus
getVolume :: SFSound a => a -> IO Float
isRelativeToListener :: SFSound a => a -> IO Bool
setAttenuation :: SFSound a => a -> Float -> IO ()
setLoop :: SFSound a => a -> Bool -> IO ()
setMinDistance :: SFSound a => a -> Float -> IO ()
setPitch :: SFSound a => a -> Float -> IO ()
setPlayingOffset :: SFSound a => a -> Time -> IO ()
setPosition :: SFSound a => a -> Vec3f -> IO ()
setRelativeToListener :: SFSound a => a -> Bool -> IO ()
setVolume :: SFSound a => a -> Float -> IO ()
module SFML.Audio.Sound
-- | Create a new sound.
createSound :: IO Sound
-- | Create a new sound by copying an existing one.
copySound :: Sound -> IO Sound
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Start or resume playing a sound.
--
-- This function starts the sound if it was stopped, resumes it if it was
-- paused, and restarts it from beginning if it was it already playing.
--
-- This function uses its own thread so that it doesn't block the rest of
-- the program while the sound is played.
play :: SFSound a => a -> IO ()
-- | Pause a sound.
--
-- This function pauses the sound if it was playing, otherwise (sound
-- already paused or stopped) it has no effect.
pause :: SFSound a => a -> IO ()
-- | Stop playing a sound.
--
-- This function stops the sound if it was playing or paused, and does
-- nothing if it was already stopped.
--
-- It also resets the playing position (unlike pause).
stop :: SFSound a => a -> IO ()
-- | Set the source buffer containing the audio data to play.
--
-- It is important to note that the sound buffer is not copied, thus the
-- SoundBuffer object must remain alive as long as it is attached
-- to the sound.
setSoundBuffer :: Sound -> SoundBuffer -> IO ()
-- | Get the audio buffer attached to a sound.
getSoundBuffer :: Sound -> IO SoundBuffer
-- | Set whether or not a sound should loop after reaching the end.
--
-- If set, the sound will restart from beginning after reaching the end
-- and so on, until it is stopped or setLoop False is
-- called.
--
-- The default looping state for sounds is false.
setLoop :: SFSound a => a -> Bool -> IO ()
-- | Tell whether or not a sound is in loop mode.
getLoop :: SFSound a => a -> IO Bool
-- | Get the current status of a sound (stopped, paused, playing).
getStatus :: SFSound a => a -> IO SoundStatus
-- | Set the pitch of a sound.
--
-- The pitch represents the perceived fundamental frequency of a sound;
-- thus you can make a sound more acute or grave by changing its pitch. A
-- side effect of changing the pitch is to modify the playing speed of
-- the sound as well.
--
-- The default value for the pitch is 1.
setPitch :: SFSound a => a -> Float -> IO ()
-- | Set the volume of a sound.
--
-- The volume is a value between 0 (mute) and 100 (full volume).
--
-- The default value for the volume is 100.
setVolume :: SFSound a => a -> Float -> IO ()
-- | Set the 3D position of a sound in the audio scene.
--
-- Only sounds with one channel (mono sounds) can be spatialized.
--
-- The default position of a sound is (0, 0, 0).
setPosition :: SFSound a => a -> Vec3f -> IO ()
-- | Make the sound's position relative to the listener or absolute.
--
-- Making a sound relative to the listener will ensure that it will
-- always be played the same way regardless the position of the listener.
-- This can be useful for non-spatialized sounds, sounds that are
-- produced by the listener, or sounds attached to it.
--
-- The default value is false (position is absolute).
setRelativeToListener :: SFSound a => a -> Bool -> IO ()
-- | Set the minimum distance of a sound.
--
-- The minimum distance of a sound is the maximum distance at which it is
-- heard at its maximum volume. Further than the minimum distance, it
-- will start to fade out according to its attenuation factor. A value of
-- 0 (inside the head of the listener) is an invalid value and is
-- forbidden.
--
-- The default value of the minimum distance is 1.
setMinDistance :: SFSound a => a -> Float -> IO ()
-- | Set the attenuation factor of a sound.
--
-- The attenuation is a multiplicative factor which makes the sound more
-- or less loud according to its distance from the listener. An
-- attenuation of 0 will produce a non-attenuated sound, i.e. its volume
-- will always be the same whether it is heard from near or from far. On
-- the other hand, an attenuation value such as 100 will make the sound
-- fade out very quickly as it gets further from the listener.
--
-- The default value of the attenuation is 1.
setAttenuation :: SFSound a => a -> Float -> IO ()
-- | Change the current playing position of a sound.
--
-- The playing position can be changed when the sound is either paused or
-- playing.
setPlayingOffset :: SFSound a => a -> Time -> IO ()
-- | Get the pitch of a sound.
getPitch :: SFSound a => a -> IO Float
-- | Get the volume of a sound.
getVolume :: SFSound a => a -> IO Float
-- | Get the 3D position of a sound in the audio scene.
getPosition :: SFSound a => a -> IO Vec3f
-- | Tell whether a sound's position is relative to the listener or is
-- absolute.
isRelativeToListener :: SFSound a => a -> IO Bool
-- | Get the minimum distance of a sound.
getMinDistance :: SFSound a => a -> IO Float
-- | Get the attenuation factor of a sound.
getAttenuation :: SFSound a => a -> IO Float
-- | Get the current playing position of a sound.
getPlayingOffset :: SFSound a => a -> IO Time
instance SFSound Sound
instance SFResource Sound
module SFML.Audio.SoundStream
-- | Defines the data to fill by the onGetData callback.
data SoundStreamChunk
SoundStreamChunk :: Ptr Word16 -> Int -> SoundStreamChunk
-- | Pointer to the audio samples
samples :: SoundStreamChunk -> Ptr Word16
-- | Number of samples pointed by Samples
sampleCount :: SoundStreamChunk -> Int
-- | Type of the callback used to get a sound stream data.
type SoundStreamGetDataCallback a = Ptr SoundStreamChunk -> Ptr a -> IO CInt
-- | Type of the callback used to seek in a sound stream.
type SoundStreamSeekCallback a = Time -> Ptr a -> IO ()
-- | Create a new sound stream.
createSoundStream :: Ptr (SoundStreamGetDataCallback a) -> Ptr (SoundStreamSeekCallback a) -> Int -> Int -> Ptr a -> IO SoundStream
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Start or resume playing a sound.
--
-- This function starts the sound if it was stopped, resumes it if it was
-- paused, and restarts it from beginning if it was it already playing.
--
-- This function uses its own thread so that it doesn't block the rest of
-- the program while the sound is played.
play :: SFSound a => a -> IO ()
-- | Pause a sound.
--
-- This function pauses the sound if it was playing, otherwise (sound
-- already paused or stopped) it has no effect.
pause :: SFSound a => a -> IO ()
-- | Stop playing a sound.
--
-- This function stops the sound if it was playing or paused, and does
-- nothing if it was already stopped.
--
-- It also resets the playing position (unlike pause).
stop :: SFSound a => a -> IO ()
-- | Get the attenuation factor of a sound.
getAttenuation :: SFSound a => a -> IO Float
-- | Tell whether or not a sound is in loop mode.
getLoop :: SFSound a => a -> IO Bool
-- | Get the minimum distance of a sound.
getMinDistance :: SFSound a => a -> IO Float
-- | Get the pitch of a sound.
getPitch :: SFSound a => a -> IO Float
-- | Get the current playing position of a sound.
getPlayingOffset :: SFSound a => a -> IO Time
-- | Get the 3D position of a sound in the audio scene.
getPosition :: SFSound a => a -> IO Vec3f
-- | Get the current status of a sound (stopped, paused, playing).
getStatus :: SFSound a => a -> IO SoundStatus
-- | Get the volume of a sound.
getVolume :: SFSound a => a -> IO Float
-- | Tell whether a sound's position is relative to the listener or is
-- absolute.
isRelativeToListener :: SFSound a => a -> IO Bool
-- | Set the attenuation factor of a sound.
--
-- The attenuation is a multiplicative factor which makes the sound more
-- or less loud according to its distance from the listener. An
-- attenuation of 0 will produce a non-attenuated sound, i.e. its volume
-- will always be the same whether it is heard from near or from far. On
-- the other hand, an attenuation value such as 100 will make the sound
-- fade out very quickly as it gets further from the listener.
--
-- The default value of the attenuation is 1.
setAttenuation :: SFSound a => a -> Float -> IO ()
-- | Set whether or not a sound should loop after reaching the end.
--
-- If set, the sound will restart from beginning after reaching the end
-- and so on, until it is stopped or setLoop False is
-- called.
--
-- The default looping state for sounds is false.
setLoop :: SFSound a => a -> Bool -> IO ()
-- | Set the minimum distance of a sound.
--
-- The minimum distance of a sound is the maximum distance at which it is
-- heard at its maximum volume. Further than the minimum distance, it
-- will start to fade out according to its attenuation factor. A value of
-- 0 (inside the head of the listener) is an invalid value and is
-- forbidden.
--
-- The default value of the minimum distance is 1.
setMinDistance :: SFSound a => a -> Float -> IO ()
-- | Set the pitch of a sound.
--
-- The pitch represents the perceived fundamental frequency of a sound;
-- thus you can make a sound more acute or grave by changing its pitch. A
-- side effect of changing the pitch is to modify the playing speed of
-- the sound as well.
--
-- The default value for the pitch is 1.
setPitch :: SFSound a => a -> Float -> IO ()
-- | Change the current playing position of a sound.
--
-- The playing position can be changed when the sound is either paused or
-- playing.
setPlayingOffset :: SFSound a => a -> Time -> IO ()
-- | Set the 3D position of a sound in the audio scene.
--
-- Only sounds with one channel (mono sounds) can be spatialized.
--
-- The default position of a sound is (0, 0, 0).
setPosition :: SFSound a => a -> Vec3f -> IO ()
-- | Make the sound's position relative to the listener or absolute.
--
-- Making a sound relative to the listener will ensure that it will
-- always be played the same way regardless the position of the listener.
-- This can be useful for non-spatialized sounds, sounds that are
-- produced by the listener, or sounds attached to it.
--
-- The default value is false (position is absolute).
setRelativeToListener :: SFSound a => a -> Bool -> IO ()
-- | Set the volume of a sound.
--
-- The volume is a value between 0 (mute) and 100 (full volume).
--
-- The default value for the volume is 100.
setVolume :: SFSound a => a -> Float -> IO ()
instance SFSound SoundStream
instance SFResource SoundStream
instance Storable SoundStreamChunk
module SFML.Audio.SFSampled
class SFSampled a
getSampleRate :: SFSampled a => a -> IO Int
module SFML.Audio.SoundBuffer
-- | Create a new sound buffer and load it from a file.
--
-- Here is a complete list of all the supported audio formats: ogg, wav,
-- flac, aiff, au, raw, paf, svx, nist, voc, ircam, w64, mat4, mat5 pvf,
-- htk, sds, avr, sd2, caf, wve, mpc2k, rf64.
soundBufferFromFile :: FilePath -> IO (Either SFException SoundBuffer)
-- | Create a new sound buffer and load it from a file in memory.
--
-- Here is a complete list of all the supported audio formats: ogg, wav,
-- flac, aiff, au, raw, paf, svx, nist, voc, ircam, w64, mat4, mat5 pvf,
-- htk, sds, avr, sd2, caf, wve, mpc2k, rf64.
soundBufferFromMemory :: Ptr a -> Int -> IO (Either SFException SoundBuffer)
-- | Create a new sound buffer and load it from a custom stream.
--
-- Here is a complete list of all the supported audio formats: ogg, wav,
-- flac, aiff, au, raw, paf, svx, nist, voc, ircam, w64, mat4, mat5 pvf,
-- htk, sds, avr, sd2, caf, wve, mpc2k, rf64.
soundBufferFromStream :: InputStream -> IO (Either SFException SoundBuffer)
-- | Create a new sound buffer and load it from an array of samples in
-- memory.
--
-- The assumed format of the audio samples is 16 bits signed integer
-- (sfInt16).
soundBufferFromSamples :: Ptr a -> Int -> Int -> Int -> IO (Maybe SoundBuffer)
-- | Create a new sound buffer by copying an existing one.
copySoundBuffer :: SoundBuffer -> IO SoundBuffer
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Save a sound buffer to an audio file.
--
-- Here is a complete list of all the supported audio formats: ogg, wav,
-- flac, aiff, au, raw, paf, svx, nist, voc, ircam, w64, mat4, mat5 pvf,
-- htk, sds, avr, sd2, caf, wve, mpc2k, rf64.
saveSoundBufferToFile :: SoundBuffer -> FilePath -> IO Bool
-- | Get the array of audio samples stored in a sound buffer.
--
-- The format of the returned samples is 16 bits signed integer
-- (sfInt16). The total number of samples in this array is given by the
-- getSampleCount function.
getSamples :: SoundBuffer -> IO (Ptr a)
-- | Get the number of samples stored in a sound buffer.
--
-- The array of samples can be accessed with the sfSoundBuffer_getSamples
-- function.
getSampleCount :: SoundBuffer -> IO Int
-- | Get the sample rate of a sound buffer.
--
-- The sample rate is the number of samples played per second. The
-- higher, the better the quality (for example, 44100 samples/s is CD
-- quality).
getSampleRate :: SFSampled a => a -> IO Int
-- | Get the number of channels used by a sound buffer.
--
-- If the sound is mono then the number of channels will be 1, 2 for
-- stereo, etc.
getChannelCount :: SFSoundBuffer a => a -> IO Int
-- | Get the total duration of a sound buffer.
getDuration :: SFSoundBuffer a => a -> IO Time
instance SFSampled SoundBuffer
instance SFSoundBuffer SoundBuffer
instance SFResource SoundBuffer
module SFML.Audio.SoundBufferRecorder
-- | Create a new sound buffer recorder.
createSoundBufferRecorder :: IO (Either SFException SoundBufferRecorder)
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Start the capture of a sound recorder.
--
-- The sample rate parameter defines the number of audio samples captured
-- per second. The higher, the better the quality (for example, 44100
-- samples/sec is CD quality).
--
-- This function uses its own thread so that it doesn't block the rest of
-- the program while the capture runs.
--
-- Please note that only one capture can happen at the same time.
--
-- Return True if start of capture was successful, False
-- otherwise.
startRecording :: SFSoundRecorder a => a -> Int -> IO Bool
-- | Stop the capture of a sound recorder.
stopRecording :: SFSoundRecorder a => a -> IO ()
-- | Get the sample rate of a sound buffer.
--
-- The sample rate is the number of samples played per second. The
-- higher, the better the quality (for example, 44100 samples/s is CD
-- quality).
getSampleRate :: SFSampled a => a -> IO Int
-- | Get the sound buffer containing the captured audio data.
--
-- The sound buffer is valid only after the capture has ended. This
-- function provides a read-only access to the internal sound buffer, but
-- it can be copied if you need to make any modification to it.
getRecorderBuffer :: SoundBufferRecorder -> IO SoundBuffer
instance SFSampled SoundBufferRecorder
instance SFSoundRecorder SoundBufferRecorder
instance SFResource SoundBufferRecorder
module SFML.Audio.SoundRecorder
-- | Type of the callback used when starting a capture.
type SoundRecorderStartCallback a = Ptr a -> IO CInt
-- | Type of the callback used to process audio data.
type SoundRecorderProcessCallback a = Ptr Word16 -> CUInt -> Ptr a -> IO Bool
-- | Type of the callback used when stopping a capture.
type SoundRecorderStopCallback a = Ptr a -> IO ()
-- | Construct a new sound recorder from callback functions.
createSoundRecorder :: Ptr (SoundRecorderStartCallback a) -> Ptr (SoundRecorderProcessCallback a) -> Ptr (SoundRecorderStopCallback a) -> Ptr a -> IO (Either SFException SoundRecorder)
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Start the capture of a sound recorder.
--
-- The sample rate parameter defines the number of audio samples captured
-- per second. The higher, the better the quality (for example, 44100
-- samples/sec is CD quality).
--
-- This function uses its own thread so that it doesn't block the rest of
-- the program while the capture runs.
--
-- Please note that only one capture can happen at the same time.
--
-- Return True if start of capture was successful, False
-- otherwise.
startRecording :: SFSoundRecorder a => a -> Int -> IO Bool
-- | Stop the capture of a sound recorder.
stopRecording :: SFSoundRecorder a => a -> IO ()
-- | Get the sample rate of a sound buffer.
--
-- The sample rate is the number of samples played per second. The
-- higher, the better the quality (for example, 44100 samples/s is CD
-- quality).
getSampleRate :: SFSampled a => a -> IO Int
-- | Check if the system supports audio capture.
--
-- This function should always be called before using the audio capture
-- features. If it returns false, then any attempt to use
-- SoundRecorder will fail.
isSoundRecorderAvailable :: IO Bool
-- | Set the processing interval.
--
-- The processing interval controls the period between calls to the
-- onProcessSamples function. You may want to use a small interval if you
-- want to process the recorded data in real time, for example.
--
-- Note: this is only a hint, the actual period may vary. So don't rely
-- on this parameter to implement precise timing.
--
-- The default processing interval is 100 ms.
setProcessingInterval :: SoundRecorder -> Time -> IO ()
-- | Get a list of the names of all availabe audio capture devices.
--
-- This function returns an array of strings (null terminated),
-- containing the names of all availabe audio capture devices. If no
-- devices are available then Nothing is returned.
getAvailableSoundRecordingDevices :: IO [String]
-- | Get the name of the default audio capture device.
--
-- This function returns the name of the default audio capture device. If
-- none is available, NULL is returned.
getDefaultSoundRecordingDevice :: IO String
-- | Set the audio capture device.
--
-- This function sets the audio capture device to the device with the
-- given name. It can be called on the fly (i.e: while recording). If you
-- do so while recording and opening the device fails, it stops the
-- recording.
--
-- Return 'True if it was able to set the requested device, False
-- otherwise.
setSoundRecordingDevice :: SoundRecorder -> String -> IO Bool
-- | Get the name of the current audio capture device.
getSoundRecordingDevice :: SoundRecorder -> IO String
instance SFSampled SoundRecorder
instance SFSoundRecorder SoundRecorder
instance SFResource SoundRecorder
module SFML.Audio.Music
-- | Create a new music and load it from a file.
--
-- This function doesn't start playing the music (call play to do
-- so).
--
-- Here is a complete list of all the supported audio formats: ogg, wav,
-- flac, aiff, au, raw, paf, svx, nist, voc, ircam, w64, mat4, mat5 pvf,
-- htk, sds, avr, sd2, caf, wve, mpc2k, rf64.
musicFromFile :: FilePath -> IO (Either SFException Music)
-- | Create a new music and load it from a file in memory.
--
-- This function doesn't start playing the music (call play to do
-- so).
--
-- Here is a complete list of all the supported audio formats: ogg, wav,
-- flac, aiff, au, raw, paf, svx, nist, voc, ircam, w64, mat4, mat5 pvf,
-- htk, sds, avr, sd2, caf, wve, mpc2k, rf64.
musicFromMemory :: Ptr a -> Int -> IO (Either SFException Music)
-- | Create a new music and load it from a custom stream.
--
-- This function doesn't start playing the music (call play to do
-- so).
--
-- Here is a complete list of all the supported audio formats: ogg, wav,
-- flac, aiff, au, raw, paf, svx, nist, voc, ircam, w64, mat4, mat5 pvf,
-- htk, sds, avr, sd2, caf, wve, mpc2k, rf64.
musicFromStream :: InputStream -> IO (Either SFException Music)
-- | Destroy the given SFML resource.
destroy :: SFResource a => a -> IO ()
-- | Set whether or not a sound should loop after reaching the end.
--
-- If set, the sound will restart from beginning after reaching the end
-- and so on, until it is stopped or setLoop False is
-- called.
--
-- The default looping state for sounds is false.
setLoop :: SFSound a => a -> Bool -> IO ()
-- | Tell whether or not a sound is in loop mode.
getLoop :: SFSound a => a -> IO Bool
-- | Get the total duration of a sound buffer.
getDuration :: SFSoundBuffer a => a -> IO Time
-- | Start or resume playing a sound.
--
-- This function starts the sound if it was stopped, resumes it if it was
-- paused, and restarts it from beginning if it was it already playing.
--
-- This function uses its own thread so that it doesn't block the rest of
-- the program while the sound is played.
play :: SFSound a => a -> IO ()
-- | Pause a sound.
--
-- This function pauses the sound if it was playing, otherwise (sound
-- already paused or stopped) it has no effect.
pause :: SFSound a => a -> IO ()
-- | Stop playing a sound.
--
-- This function stops the sound if it was playing or paused, and does
-- nothing if it was already stopped.
--
-- It also resets the playing position (unlike pause).
stop :: SFSound a => a -> IO ()
-- | Get the number of channels used by a sound buffer.
--
-- If the sound is mono then the number of channels will be 1, 2 for
-- stereo, etc.
getChannelCount :: SFSoundBuffer a => a -> IO Int
-- | Get the sample rate of a sound buffer.
--
-- The sample rate is the number of samples played per second. The
-- higher, the better the quality (for example, 44100 samples/s is CD
-- quality).
getSampleRate :: SFSampled a => a -> IO Int
-- | Get the current status of a sound (stopped, paused, playing).
getStatus :: SFSound a => a -> IO SoundStatus
-- | Get the current playing position of a sound.
getPlayingOffset :: SFSound a => a -> IO Time
-- | Set the pitch of a sound.
--
-- The pitch represents the perceived fundamental frequency of a sound;
-- thus you can make a sound more acute or grave by changing its pitch. A
-- side effect of changing the pitch is to modify the playing speed of
-- the sound as well.
--
-- The default value for the pitch is 1.
setPitch :: SFSound a => a -> Float -> IO ()
-- | Set the volume of a sound.
--
-- The volume is a value between 0 (mute) and 100 (full volume).
--
-- The default value for the volume is 100.
setVolume :: SFSound a => a -> Float -> IO ()
-- | Set the 3D position of a sound in the audio scene.
--
-- Only sounds with one channel (mono sounds) can be spatialized.
--
-- The default position of a sound is (0, 0, 0).
setPosition :: SFSound a => a -> Vec3f -> IO ()
-- | Make the sound's position relative to the listener or absolute.
--
-- Making a sound relative to the listener will ensure that it will
-- always be played the same way regardless the position of the listener.
-- This can be useful for non-spatialized sounds, sounds that are
-- produced by the listener, or sounds attached to it.
--
-- The default value is false (position is absolute).
setRelativeToListener :: SFSound a => a -> Bool -> IO ()
-- | Set the minimum distance of a sound.
--
-- The minimum distance of a sound is the maximum distance at which it is
-- heard at its maximum volume. Further than the minimum distance, it
-- will start to fade out according to its attenuation factor. A value of
-- 0 (inside the head of the listener) is an invalid value and is
-- forbidden.
--
-- The default value of the minimum distance is 1.
setMinDistance :: SFSound a => a -> Float -> IO ()
-- | Set the attenuation factor of a sound.
--
-- The attenuation is a multiplicative factor which makes the sound more
-- or less loud according to its distance from the listener. An
-- attenuation of 0 will produce a non-attenuated sound, i.e. its volume
-- will always be the same whether it is heard from near or from far. On
-- the other hand, an attenuation value such as 100 will make the sound
-- fade out very quickly as it gets further from the listener.
--
-- The default value of the attenuation is 1.
setAttenuation :: SFSound a => a -> Float -> IO ()
-- | Change the current playing position of a sound.
--
-- The playing position can be changed when the sound is either paused or
-- playing.
setPlayingOffset :: SFSound a => a -> Time -> IO ()
-- | Get the pitch of a sound.
getPitch :: SFSound a => a -> IO Float
-- | Get the volume of a sound.
getVolume :: SFSound a => a -> IO Float
-- | Get the 3D position of a sound in the audio scene.
getPosition :: SFSound a => a -> IO Vec3f
-- | Tell whether a sound's position is relative to the listener or is
-- absolute.
isRelativeToListener :: SFSound a => a -> IO Bool
-- | Get the minimum distance of a sound.
getMinDistance :: SFSound a => a -> IO Float
-- | Get the attenuation factor of a sound.
getAttenuation :: SFSound a => a -> IO Float
instance SFSound Music
instance SFSampled Music
instance SFSoundBuffer Music
instance SFResource Music
module SFML.Audio.Listener
-- | Change the global volume of all the sounds and musics.
--
-- The volume is a number between 0 and 100; it is combined with the
-- individual volume of each sound or music.
--
-- The default value for the volume is 100 (maximum).
setGlobalVolume :: Float -> IO ()
-- | Get the current value of the global volume.
getGlobalVolume :: IO Float
-- | Set the position of the listener in the scene.
--
-- The default listener's position is (0, 0, 0).
setListenerPosition :: Vec3f -> IO ()
-- | Get the current position of the listener in the scene.
getListenerPosition :: IO Vec3f
-- | Set the orientation of the forward vector in the scene.
--
-- The direction (also called "at vector") is the vector pointing forward
-- from the listener's perspective. Together with the up vector, it
-- defines the 3D orientation of the listener in the scene. The direction
-- vector doesn't have to be normalized.
--
-- The default listener's direction is (0, 0, -1).
setListenerDirection :: Vec3f -> IO ()
-- | Get the current orientation of the listener in the scene.
getListenerDirection :: IO Vec3f
-- | Set the upward vector of the listener in the scene
--
-- The up vector is the vector that points upward from the listener's
-- perspective. Together with the direction, it defines the 3D
-- orientation of the listener in the scene. The up vector doesn't have
-- to be normalized. The default listener's up vector is (0, 1, 0). It is
-- usually not necessary to change it, especially in 2D scenarios.
setListenerUpVector :: Vec3f -> IO ()
-- | Get the current upward vector (unnormalised) of the listener in the
-- scene.
getListenerUpVector :: IO Vec3f
module SFML.Audio