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)
data ScratchOptions =
ScratchOptions {
ScratchOptions -> Bool
tab :: Bool,
ScratchOptions -> Bool
vertical :: Bool,
ScratchOptions -> Bool
wrap :: Bool,
ScratchOptions -> Bool
focus :: Bool,
ScratchOptions -> Bool
resize :: Bool,
ScratchOptions -> Bool
bottom :: Bool,
ScratchOptions -> Bool
modify :: Bool,
ScratchOptions -> Maybe FloatOptions
float :: Maybe FloatOptions,
ScratchOptions -> Maybe Int
size :: Maybe Int,
ScratchOptions -> Maybe Int
maxSize :: Maybe Int,
ScratchOptions -> [Syntax]
syntax :: [Syntax],
ScratchOptions -> [Mapping]
mappings :: [Mapping],
ScratchOptions -> Maybe Text
filetype :: Maybe Text,
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)
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"