-----------------------------------------------------------------------------
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Miso.Lynx.Element.Text.Method
-- Copyright   :  (C) 2016-2025 David M. Johnson
-- License     :  BSD3-style (see the file LICENSE)
-- Maintainer  :  David M. Johnson <code@dmj.io>
-- Stability   :  experimental
-- Portability :  non-portable
----------------------------------------------------------------------------
module Miso.Lynx.Element.Text.Method
  ( -- *** Methods
    setTextSelection
  , getTextBoundingRect
  , getSelectedText
  -- *** Types
  , SetTextSelection (..)
  -- *** Smart constructors
  , defaultGetTextBoundingRect
  ) where
-----------------------------------------------------------------------------
import           Miso
import           Miso.Lynx.FFI (invokeExec)
-----------------------------------------------------------------------------
import           Language.Javascript.JSaddle
-----------------------------------------------------------------------------
data SetTextSelection
  = SetTextSelection
  { SetTextSelection -> Double
startX, SetTextSelection -> Double
startY :: Double
  -- ^ X/Y-coordinate of the selection start relative to the element
  , SetTextSelection -> Double
endX, SetTextSelection -> Double
endY :: Double
  -- ^ X/Y-coordinate of the selection end relative to the element
  , SetTextSelection -> Bool
showStartHandle, SetTextSelection -> Bool
showEndHandle :: Bool
  -- ^ Whether to show or hide the start/end handle
  }
-----------------------------------------------------------------------------
instance ToJSVal SetTextSelection where
  toJSVal :: SetTextSelection -> JSM JSVal
toJSVal SetTextSelection {Bool
Double
startX :: SetTextSelection -> Double
startY :: SetTextSelection -> Double
endX :: SetTextSelection -> Double
endY :: SetTextSelection -> Double
showStartHandle :: SetTextSelection -> Bool
showEndHandle :: SetTextSelection -> Bool
startX :: Double
startY :: Double
endX :: Double
endY :: Double
showStartHandle :: Bool
showEndHandle :: Bool
..} = do
    o <- JSM Object
create
    set "startX" startX o
    set "startY" startY o
    set "endX" endX o
    set "endY" endY o
    set "showStartHandle" showStartHandle o
    set "showEndHandle" showEndHandle o
    toJSVal o
-----------------------------------------------------------------------------
-- | <https://lynxjs.org/api/elements/built-in/text.html#setTextSelection>
--
-- This method sets the selected text based on start and end positions and controls the visibility of selection handles. The response res contains:
--
-- @
--
-- data Action = SetText | TextSet | SetTextError MisoString
--
-- update :: Action -> Effect model Action
-- update SetText = setTextSelection "someImageId" SetText SetTextError
-- update TextSet = io_ (consoleLog "text was set")
-- update (SetTextError e) = io_ (consoleLog e)
--
-- @
--
setTextSelection
  :: MisoString
  -> SetTextSelection
  -> action
  -> (MisoString -> action)
  -> Effect parent model action
setTextSelection :: forall action parent model.
MisoString
-> SetTextSelection
-> action
-> (MisoString -> action)
-> Effect parent model action
setTextSelection MisoString
selector SetTextSelection
params action
action =
  MisoString
-> MisoString
-> SetTextSelection
-> (() -> action)
-> (MisoString -> action)
-> Effect parent model action
forall params argument action parent model.
(ToJSVal params, FromJSVal argument) =>
MisoString
-> MisoString
-> params
-> (argument -> action)
-> (MisoString -> action)
-> Effect parent model action
invokeExec MisoString
"setTextSelection" MisoString
selector SetTextSelection
params (\() -> action
action)
-----------------------------------------------------------------------------
data GetTextBoundingRect
  = GetTextBoundingRect
  { GetTextBoundingRect -> Double
start, GetTextBoundingRect -> Double
end :: Double
  -- ^ X/Y-coordinate of the selection start relative to the element
  }
-----------------------------------------------------------------------------
instance ToJSVal GetTextBoundingRect where
  toJSVal :: GetTextBoundingRect -> JSM JSVal
toJSVal GetTextBoundingRect {Double
start :: GetTextBoundingRect -> Double
end :: GetTextBoundingRect -> Double
start :: Double
end :: Double
..} = do
    o <- JSM Object
create
    set "start" start o
    set "end" end o
    toJSVal o
-----------------------------------------------------------------------------
defaultGetTextBoundingRect :: GetTextBoundingRect
defaultGetTextBoundingRect :: GetTextBoundingRect
defaultGetTextBoundingRect = Double -> Double -> GetTextBoundingRect
GetTextBoundingRect Double
0 Double
0
-----------------------------------------------------------------------------
-- | https://lynxjs.org/api/elements/built-in/text.html#gettextboundingrect
--
-- This method retrieves the bounding box of a specific range of text.
--
-- @
--
-- data Action = RectReceived Rect | GetRect | GotError MisoString
--
-- update :: Action -> Effect model Action
-- update GetRect = getTextBoundingRect "#box" defaultGetTextBoundingRect RectReceived GotError
-- update (RectReceived rect) = io_ $ consoleLog ("got rect")
-- update (GotError errMsg) = io_ (consoleLog errMsg)
--
-- @
--
getTextBoundingRect
  :: MisoString
  -> GetTextBoundingRect
  -> (JSVal -> action)
  -> (MisoString -> action)
  -> Effect parent model action
getTextBoundingRect :: forall action parent model.
MisoString
-> GetTextBoundingRect
-> (JSVal -> action)
-> (MisoString -> action)
-> Effect parent model action
getTextBoundingRect = MisoString
-> MisoString
-> GetTextBoundingRect
-> (JSVal -> action)
-> (MisoString -> action)
-> Effect parent model action
forall params argument action parent model.
(ToJSVal params, FromJSVal argument) =>
MisoString
-> MisoString
-> params
-> (argument -> action)
-> (MisoString -> action)
-> Effect parent model action
invokeExec MisoString
"getTextBoundingRect"
-----------------------------------------------------------------------------
-- | https://lynxjs.org/api/elements/built-in/text.html#getselectedtext
--
-- This method retrieves the string content of the currently selected text.
--
-- @
--
-- data Action = TextReceived MisoString | GetText | GotError MisoString
--
-- update :: Action -> Effect model Action
-- update GetText = getSelectedText "#box" TextReceived GotError
-- update (TextReceived txt) = io_ (consoleLog ("got text: " <> txt))
-- update (GotError errMsg) = io_ (consoleLog errMsg)
--
-- @
--
getSelectedText
  :: MisoString
  -> (MisoString -> action)
  -> (MisoString -> action)
  -> Effect parent model action
getSelectedText :: forall action parent model.
MisoString
-> (MisoString -> action)
-> (MisoString -> action)
-> Effect parent model action
getSelectedText MisoString
selector = MisoString
-> MisoString
-> ()
-> (MisoString -> action)
-> (MisoString -> action)
-> Effect parent model action
forall params argument action parent model.
(ToJSVal params, FromJSVal argument) =>
MisoString
-> MisoString
-> params
-> (argument -> action)
-> (MisoString -> action)
-> Effect parent model action
invokeExec MisoString
"getSelectedText" MisoString
selector ()
-----------------------------------------------------------------------------