-- |Scratch buffer configuration.
module Ribosome.Data.ScratchOptions where

import Ribosome.Data.FloatOptions (FloatOptions)
import Ribosome.Data.Mapping (Mapping)
import Ribosome.Data.ScratchId (ScratchId)
import Ribosome.Data.Syntax (Syntax)

-- |Configure the visual properties of a scratch buffer.
-- If the option @float@ is specified, the buffer will be opened in a floating window.
data ScratchOptions =
  ScratchOptions {
    -- |Whether to open the buffer in a new tab.
    ScratchOptions -> Bool
tab :: Bool,
    -- |Whether to split the current window vertically, only relevant for non-floating windows.
    ScratchOptions -> Bool
vertical :: Bool,
    -- |Whether to set the @wrap@ option in the window, to disable breaking long lines.
    ScratchOptions -> Bool
wrap :: Bool,
    -- |Whether to move the cursor to the window after opening it.
    ScratchOptions -> Bool
focus :: Bool,
    -- |Whether to adapt the buffer's size to the number of lines, for horizontal splits.
    ScratchOptions -> Bool
resize :: Bool,
    -- |Whether to place the window at the bottom of the stack, only relevant for non-floating windows.
    ScratchOptions -> Bool
bottom :: Bool,
    -- |Whether to set the @modifiable@ option for the buffer.
    ScratchOptions -> Bool
modify :: Bool,
    -- |If 'Just', creates a floating window with the given config.
    ScratchOptions -> Maybe FloatOptions
float :: Maybe FloatOptions,
    -- |The initial size of the window.
    ScratchOptions -> Maybe Int
size :: Maybe Int,
    -- |When resizing automatically, do not exceed this size.
    ScratchOptions -> Maybe Int
maxSize :: Maybe Int,
    -- |A set of syntax rules to apply to the buffer.
    ScratchOptions -> [Syntax]
syntax :: [Syntax],
    -- |A set of key mappings to define buffer-locally. See [Ribosome.Mappings]("Ribosome#g:mappings").
    ScratchOptions -> [Mapping]
mappings :: [Mapping],
    -- |The value for the @filetype@ option.
    ScratchOptions -> Maybe Text
filetype :: Maybe Text,
    -- |The ID of the scratch buffer.
    ScratchOptions -> ScratchId
name :: ScratchId
  }
  deriving stock (ScratchOptions -> ScratchOptions -> Bool
(ScratchOptions -> ScratchOptions -> Bool)
-> (ScratchOptions -> ScratchOptions -> Bool) -> Eq ScratchOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScratchOptions -> ScratchOptions -> Bool
$c/= :: ScratchOptions -> ScratchOptions -> Bool
== :: ScratchOptions -> ScratchOptions -> Bool
$c== :: ScratchOptions -> ScratchOptions -> Bool
Eq, Int -> ScratchOptions -> ShowS
[ScratchOptions] -> ShowS
ScratchOptions -> String
(Int -> ScratchOptions -> ShowS)
-> (ScratchOptions -> String)
-> ([ScratchOptions] -> ShowS)
-> Show ScratchOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScratchOptions] -> ShowS
$cshowList :: [ScratchOptions] -> ShowS
show :: ScratchOptions -> String
$cshow :: ScratchOptions -> String
showsPrec :: Int -> ScratchOptions -> ShowS
$cshowsPrec :: Int -> ScratchOptions -> ShowS
Show, (forall x. ScratchOptions -> Rep ScratchOptions x)
-> (forall x. Rep ScratchOptions x -> ScratchOptions)
-> Generic ScratchOptions
forall x. Rep ScratchOptions x -> ScratchOptions
forall x. ScratchOptions -> Rep ScratchOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ScratchOptions x -> ScratchOptions
$cfrom :: forall x. ScratchOptions -> Rep ScratchOptions x
Generic)

-- |The default configuration, setting all flags to 'False' except for 'resize' and 'bottom', and everything else to
-- 'mempty'.
scratch :: ScratchId -> ScratchOptions
scratch :: ScratchId -> ScratchOptions
scratch ScratchId
name =
  ScratchOptions :: Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Maybe FloatOptions
-> Maybe Int
-> Maybe Int
-> [Syntax]
-> [Mapping]
-> Maybe Text
-> ScratchId
-> ScratchOptions
ScratchOptions {
      $sel:tab:ScratchOptions :: Bool
tab = Bool
False,
      $sel:vertical:ScratchOptions :: Bool
vertical = Bool
False,
      $sel:wrap:ScratchOptions :: Bool
wrap = Bool
False,
      $sel:focus:ScratchOptions :: Bool
focus = Bool
False,
      $sel:resize:ScratchOptions :: Bool
resize = Bool
True,
      $sel:bottom:ScratchOptions :: Bool
bottom = Bool
True,
      $sel:modify:ScratchOptions :: Bool
modify = Bool
False,
      $sel:float:ScratchOptions :: Maybe FloatOptions
float = Maybe FloatOptions
forall a. Maybe a
Nothing,
      $sel:size:ScratchOptions :: Maybe Int
size = Maybe Int
forall a. Maybe a
Nothing,
      $sel:maxSize:ScratchOptions :: Maybe Int
maxSize = Maybe Int
forall a. Maybe a
Nothing,
      $sel:syntax:ScratchOptions :: [Syntax]
syntax = [],
      $sel:mappings:ScratchOptions :: [Mapping]
mappings = [],
      $sel:filetype:ScratchOptions :: Maybe Text
filetype = Maybe Text
forall a. Maybe a
Nothing,
      ScratchId
name :: ScratchId
$sel:name:ScratchOptions :: ScratchId
..
    }

instance Default ScratchOptions where
  def :: ScratchOptions
def =
    ScratchId -> ScratchOptions
scratch ScratchId
"scratch"