-- |The effect 'Settings' abstracts Neovim variables
module Ribosome.Effect.Settings where

import Prelude hiding (get)

import Ribosome.Data.Setting (Setting)
import Ribosome.Data.SettingError (SettingError)
import Ribosome.Host.Class.Msgpack.Decode (MsgpackDecode)
import Ribosome.Host.Class.Msgpack.Encode (MsgpackEncode)

-- |This effects abstracts Neovim variables with associated defaults.
data Settings :: Effect where
  -- |Get the value of the setting's Neovim variable or return the default if it is undefined.
  Get :: MsgpackDecode a => Setting a -> Settings m a
  -- |Set the value of the setting's Neovim variable.
  Update :: MsgpackEncode a => Setting a -> a -> Settings m ()

makeSem_ ''Settings

-- |Get the value of the setting's Neovim variable or return the default if it is undefined.
get ::
   a r .
  MsgpackDecode a =>
  Member Settings r =>
  Setting a ->
  Sem r a

-- |Set the value of the setting's Neovim variable.
update ::
   a r .
  MsgpackEncode a =>
  Member Settings r =>
  Setting a ->
  a ->
  Sem r ()

-- |Get the setting's value or return the supplied fallback value if the Neovim variable is undefined and the setting
-- has no default value.
or ::
  MsgpackDecode a =>
  Member (Settings !! SettingError) r =>
  a ->
  Setting a ->
  Sem r a
or :: forall a (r :: EffectRow).
(MsgpackDecode a, Member (Settings !! SettingError) r) =>
a -> Setting a -> Sem r a
or a
a Setting a
s =
  a
a a -> Sem (Settings : r) a -> Sem r a
forall err (eff :: Effect) (r :: EffectRow) a.
Member (Resumable err eff) r =>
a -> Sem (eff : r) a -> Sem r a
<! Setting a -> Sem (Settings : r) a
forall a (r :: EffectRow).
(MsgpackDecode a, Member Settings r) =>
Setting a -> Sem r a
get Setting a
s

-- |Get 'Just' the setting's value or return 'Nothing' if the Neovim variable is undefined and the setting has no
-- default value.
maybe ::
  MsgpackDecode a =>
  Member (Settings !! SettingError) r =>
  Setting a ->
  Sem r (Maybe a)
maybe :: forall a (r :: EffectRow).
(MsgpackDecode a, Member (Settings !! SettingError) r) =>
Setting a -> Sem r (Maybe a)
maybe Setting a
s =
  Maybe a
forall a. Maybe a
Nothing Maybe a -> Sem (Settings : r) (Maybe a) -> Sem r (Maybe a)
forall err (eff :: Effect) (r :: EffectRow) a.
Member (Resumable err eff) r =>
a -> Sem (eff : r) a -> Sem r a
<! (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a)
-> Sem (Settings : r) a -> Sem (Settings : r) (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Setting a -> Sem (Settings : r) a
forall a (r :: EffectRow).
(MsgpackDecode a, Member Settings r) =>
Setting a -> Sem r a
get Setting a
s)