ribosome-host-0.9.9.9: Neovim plugin host for Polysemy
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ribosome.Host.Data.Report

Description

Data structures related to logging and notifying the user

Synopsis

Documentation

newtype ReportContext Source #

The provenance of a report, for use in logs.

Constructors

ReportContext 

Fields

reportContext' :: ReportContext -> Maybe Text Source #

Render a ReportContext by interspersing it with dots, returning Nothing if it is empty.

prefixReportContext' :: ReportContext -> Maybe Text Source #

Render a ReportContext by interspersing it with dots, followed by a colon, returning Nothing if it is empty.

reportContext :: ReportContext -> Text Source #

Render a ReportContext by interspersing it with dots, using global if it is empty.

prefixReportContext :: ReportContext -> Text Source #

Render a ReportContext by interspersing it with dots, followed by a colon, using global if it is empty.

data Report where Source #

An report with different messages intended to be sent to Neovim and the log, respectively.

Used by request handlers and expected by the RPC dispatcher.

Also contains the Severity of the report, or minimum log level, which determines whether the report should be logged and echoed in Neovim, and what kind of highlighting should be used in Neovim (red for errors, orange for warnings, none for infomrational errors).

The log message may span multiple lines.

Constructors

Report 

Fields

Instances

Instances details
IsString Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

fromString :: String -> Report #

Show Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Reportable Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

MsgpackEncode a => HandlerCodec (Handler r a) r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

data LogReport Source #

The type used by request handlers and expected by the RPC dispatcher.

Constructors

LogReport 

Fields

Instances

Instances details
IsString LogReport Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Generic LogReport Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Associated Types

type Rep LogReport :: Type -> Type #

Show LogReport Source # 
Instance details

Defined in Ribosome.Host.Data.Report

type Rep LogReport Source # 
Instance details

Defined in Ribosome.Host.Data.Report

type Rep LogReport = D1 ('MetaData "LogReport" "Ribosome.Host.Data.Report" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'False) (C1 ('MetaCons "LogReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "report") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Report) :*: S1 ('MetaSel ('Just "echo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "store") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "context") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReportContext))))

simple :: HasCallStack => Text -> LogReport Source #

Construct a LogReport error from a single Text.

basicReport :: Member (Stop Report) r => HasCallStack => Text -> [Text] -> Sem r a Source #

Stop with a LogReport.

class Reportable e where Source #

The class of types that are convertible to a Report.

This is used to create a uniform format for handlers, since control flow is passed on to the internal machinery when they return. If an error would be thrown that is not caught by the request dispatcher, the entire plugin would stop, so all Stop and Resumable effects need to be converted to Report before returning (see Errors).

The combinators associated with this class make this task a little less arduous:

data NumbersError = InvalidNumber

instance Reportable NumbersError where
  toReport InvalidNumber = Report "Invalid number!" ["The user entered an invalid number"] Warn

count :: Int -> Sem r Int
count i =
  resumeReport @Rpc $ mapReport @NumbersError do
    when (i == 0) (stop InvalidNumber)
    nvimGetVar ("number_" <> show i)

Here resumeReport converts a potential RpcError from nvimGetVar to Report (e.g. if the variable is not set), while mapReport uses the instance Reportable NumbersError to convert the call to stop.

Methods

toReport :: e -> Report Source #

Instances

Instances details
Reportable Void Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

toReport :: Void -> Report Source #

Reportable DecodeError Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Error

Reportable Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Reportable RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

mapReport :: forall e r a. Reportable e => Member (Stop Report) r => Sem (Stop e ': r) a -> Sem r a Source #

Reinterpret Stop err to Stop Report if err is an instance of Reportable.

type Stops errs = FMap (Pure1 Stop) @@ errs Source #

class MapReports (errs :: [Type]) (r :: EffectRow) where Source #

Map multiple errors to Report.

Methods

mapReports :: InterpretersFor (Stops errs) r Source #

Map multiple errors to Report. This needs the errors specified as type applications.

mapReports @[RpcError, SettingError]

Instances

Instances details
MapReports ('[] :: [Type]) r Source # 
Instance details

Defined in Ribosome.Host.Data.Report

(Reportable err, MapReports errs r, Member (Stop Report) (Stops errs ++ r)) => MapReports (err ': errs) r Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

mapReports :: InterpretersFor (Stops (err ': errs)) r Source #

resumeReport :: forall eff e r a. Reportable e => Members [eff !! e, Stop Report] r => Sem (eff ': r) a -> Sem r a Source #

Convert the effect eff to Resumable err eff and Stop Report if err is an instance of Reportable.

class ResumeReports (effs :: EffectRow) (errs :: [Type]) (r :: EffectRow) where Source #

Resume multiple effects as Reports.

Methods

resumeReports :: InterpretersFor effs r Source #

Resume multiple effects as Reports. This needs both effects and errors specified as type applications (though only the shape for the errors).

resumeReports @[Rpc, Settings] @[_, _]

Instances

Instances details
ResumeReports ('[] :: [Effect]) ('[] :: [Type]) r Source # 
Instance details

Defined in Ribosome.Host.Data.Report

(Reportable err, ResumeReports effs errs r, Members '[eff !! err, Stop Report] (effs ++ r)) => ResumeReports (eff ': effs) (err ': errs) r Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

resumeReports :: InterpretersFor (eff ': effs) r Source #

reportMessages :: Report -> Text Source #

Extract both user and log messages from an Report, for use in tests.

userReport :: forall e. Reportable e => e -> Text Source #

Extract the user message from an instance of Reportable.

resumeHoistUserMessage :: forall err eff err' r. Reportable err => Members [eff !! err, Stop err'] r => (Text -> err') -> InterpreterFor eff r Source #

Resume an effect with an error that's an instance of Reportable by passing its user message to a function.

mapUserMessage :: forall err err' r. Reportable err => Member (Stop err') r => (Text -> err') -> InterpreterFor (Stop err) r Source #

Map an error that's an instance of Reportable by passing its user message to a function.

stopReportToFail :: forall e r. Member Fail r => Reportable e => InterpreterFor (Stop e) r Source #

Convert an error that's an instance of Reportable to Fail, for use in tests.

resumeReportFail :: forall eff err r. Members [Fail, eff !! err] r => Reportable err => InterpreterFor eff r Source #

Resume an effect with an error that's an instance of Reportable by reinterpreting to Fail, for use in tests.