-- |Persisting data across vim sessions
module Ribosome.Effect.Persist where

import Path (File, Path, Rel)

-- |This effect abstracts storing data of type @a@ in the file system to allow loading it when a plugin starts.
--
-- Each distinct type corresponds to a separate copy of this effect. When the same type should be stored in separate
-- files for different components of the plugin, use 'Tagged'.
-- The subdirectory or file name used for a type is specified to the interpreter.
-- If the constructor 'store' is called with 'Just' a file name, each value is stored in a separate file, otherwise the
-- same file is overwritten on every call to 'store'.
--
-- The default interpreter delegates file path resolution to the effect 'Ribosome.Persist.PersistPath' and uses JSON to
-- codec the data.
data Persist a :: Effect where
  -- |Store a value in the persistence file or, if the first argument is 'Just', in that file in the persistence
  -- directory.
  Store :: Maybe (Path Rel File) -> a -> Persist a m ()
  -- |Load a value from the persistence file or, if the first argument is 'Just', from that file in the persistence
  -- directory.
  -- Returns 'Nothing' if the file doesn't exist.
  Load :: Maybe (Path Rel File) -> Persist a m (Maybe a)

makeSem_ ''Persist

-- |Store a value in the persistence file or, if the first argument is 'Just', in that file in the persistence
-- directory.
store ::
   a r .
  Member (Persist a) r =>
  Maybe (Path Rel File) ->
  a ->
  Sem r ()

-- |Load a value from the persistence file or, if the first argument is 'Just', from that file in the persistence
-- directory.
-- Returns 'Nothing' if the file doesn't exist.
load ::
   a r .
  Member (Persist a) r =>
  Maybe (Path Rel File) ->
  Sem r (Maybe a)

-- |Load a value from the persistence file or, if the first argument is 'Just', from that file in the persistence
-- directory.
-- Returns the fallback value if the file doesn't exist.
loadOr ::
  Member (Persist a) r =>
  Maybe (Path Rel File) ->
  a ->
  Sem r a
loadOr :: forall a (r :: EffectRow).
Member (Persist a) r =>
Maybe (Path Rel File) -> a -> Sem r a
loadOr Maybe (Path Rel File)
path a
a =
  a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
a (Maybe a -> a) -> Sem r (Maybe a) -> Sem r a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Path Rel File) -> Sem r (Maybe a)
forall a (r :: EffectRow).
Member (Persist a) r =>
Maybe (Path Rel File) -> Sem r (Maybe a)
load Maybe (Path Rel File)
path

-- |Load a value from the persistence file.
-- Returns 'Nothing' if the file doesn't exist.
loadSingle ::
  Member (Persist a) r =>
  Sem r (Maybe a)
loadSingle :: forall a (r :: EffectRow). Member (Persist a) r => Sem r (Maybe a)
loadSingle =
  Maybe (Path Rel File) -> Sem r (Maybe a)
forall a (r :: EffectRow).
Member (Persist a) r =>
Maybe (Path Rel File) -> Sem r (Maybe a)
load Maybe (Path Rel File)
forall a. Maybe a
Nothing

-- |Load a value from the persistence file.
-- Returns the fallback value if the file doesn't exist.
loadSingleOr ::
  Member (Persist a) r =>
  a ->
  Sem r a
loadSingleOr :: forall a (r :: EffectRow). Member (Persist a) r => a -> Sem r a
loadSingleOr a
a =
  a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
a (Maybe a -> a) -> Sem r (Maybe a) -> Sem r a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Sem r (Maybe a)
forall a (r :: EffectRow). Member (Persist a) r => Sem r (Maybe a)
loadSingle

-- |Load a value from the specified file in the persistence directory.
-- Returns 'Nothing' if the file doesn't exist.
loadPath ::
  Member (Persist a) r =>
  Path Rel File ->
  Sem r (Maybe a)
loadPath :: forall a (r :: EffectRow).
Member (Persist a) r =>
Path Rel File -> Sem r (Maybe a)
loadPath Path Rel File
path =
  Maybe (Path Rel File) -> Sem r (Maybe a)
forall a (r :: EffectRow).
Member (Persist a) r =>
Maybe (Path Rel File) -> Sem r (Maybe a)
load (Path Rel File -> Maybe (Path Rel File)
forall a. a -> Maybe a
Just Path Rel File
path)

-- |Load a value from the specified file in the persistence directory.
-- Returns the fallback value if the file doesn't exist.
loadPathOr ::
  Member (Persist a) r =>
  Path Rel File ->
  a ->
  Sem r a
loadPathOr :: forall a (r :: EffectRow).
Member (Persist a) r =>
Path Rel File -> a -> Sem r a
loadPathOr Path Rel File
path a
a =
  a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
a (Maybe a -> a) -> Sem r (Maybe a) -> Sem r a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Path Rel File -> Sem r (Maybe a)
forall a (r :: EffectRow).
Member (Persist a) r =>
Path Rel File -> Sem r (Maybe a)
loadPath Path Rel File
path