使用 EitherT 累积错误

2023-11-26

我有以下一个 Web API 的小型示例应用程序,它需要一个巨大的 JSON 文档,并且应该将其分段解析并报告每个部分的错误消息。

以下代码是使用 EitherT (和错误包)的工作示例。但是,那problem是 EitherT 打破了遇到的第一个 Left 的计算,只返回它看到的第一个“错误”。我想要的是一个错误消息列表,所有可能产生的消息。例如,如果第一行runEitherT失败了,那么就没有什么可以做的了。但如果第二行失败,那么我们仍然可以尝试运行后续行,因为它们对第二行没有数据依赖性。所以理论上我们可以产生more(不一定是全部)错误消息一次性出现。

是否可以延迟运行所有计算并返回我们可以找到的所有错误消息?

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Data.ByteString.Lazy.Char8 (pack)
import Web.Scotty as S
import Network.Wai.Middleware.RequestLogger
import Data.Aeson
import Data.Aeson.Types
import Control.Lens hiding ((.=), (??))
import Data.Aeson.Lens
import qualified Data.Text as T
import Control.Error
import Control.Applicative
import qualified Data.HashMap.Strict as H
import Network.HTTP.Types

data TypeOne = TypeOne T.Text TypeTwo TypeThree
  deriving (Show)

data TypeTwo = TypeTwo Double
  deriving (Show)

data TypeThree = TypeThree Double
  deriving (Show)

main :: IO ()
main = scotty 3000 $ do
  middleware logStdoutDev

  post "/pdor" $ do
    api_key <- param "api_key"
    input   <- param "input"

    typeOne <- runEitherT $ do
      result       <- (decode (pack input) :: Maybe Value) ?? "Could not parse. Input JSON document is malformed"
      typeTwoObj   <- (result ^? key "typeTwo")            ?? "Could not find key typeTwo in JSON document."
      typeThreeObj <- (result ^? key "typeThree")          ?? "Could not find key typeThree in JSON document."
      name         <- (result ^? key "name" . _String)     ?? "Could not find key name in JSON document."
      typeTwo      <- hoistEither $ prependLeft "Error when parsing TypeTwo: " $ parseEither jsonTypeTwo typeTwoObj
      typeThree    <- hoistEither $ prependLeft "Error when parsing TypeThree: " $ parseEither jsonTypeThree typeThreeObj

      return $ TypeOne name typeTwo typeThree

    case typeOne of
      Left errorMsg -> do
        _ <- status badRequest400
        S.json $ object ["error" .= errorMsg]
      Right _ ->
        -- do something with the parsed Haskell type
        S.json $ object ["api_key" .= (api_key :: String), "message" .= ("success" :: String)]

prependLeft :: String -> Either String a -> Either String a
prependLeft msg (Left s) = Left (msg ++ s)
prependLeft _ x = x

jsonTypeTwo :: Value -> Parser TypeTwo
jsonTypeTwo (Object v) = TypeTwo <$> v .: "val"
jsonTypeTwo _ = fail $ "no data present for TypeTwo"

jsonTypeThree :: Value -> Parser TypeThree
jsonTypeThree (Object v) = TypeThree <$> v .: "val"
jsonTypeThree _ = fail $ "no data present for TypeThree"

如果有人有重构建议,也可以接受。


正如我在评论中提到的,至少有两种累积错误的方法。下面我详细阐述一下这些。我们需要这些导入:

import Control.Applicative
import Data.Monoid
import Data.These

TheseT单子变压器

免责声明: TheseT叫做ChronicleT in these package.

看看下面的定义These数据类型:

data These a b = This a | That b | These a b

Here This and That相当于Left and Right of Either数据类型。These数据构造函数能够积累能力Monad实例:它包含两个结果(类型为b)和以前的错误的集合(类型的集合a).

利用现有的定义These我们可以轻松创建的数据类型ErrorT-类似单子变压器:

newtype TheseT e m a = TheseT {
  runTheseT :: m (These e a)
}

TheseT是一个实例Monad通过以下方式:

instance Functor m => Functor (TheseT e m) where
  fmap f (TheseT m) = TheseT (fmap (fmap f) m)

instance (Monoid e, Applicative m) => Applicative (TheseT e m) where
  pure x = TheseT (pure (pure x))
  TheseT f <*> TheseT x = TheseT (liftA2 (<*>) f x)

instance (Monoid e, Monad m) => Monad (TheseT e m) where
  return x = TheseT (return (return x))
  m >>= f = TheseT $ do
    t <- runTheseT m
    case t of
      This  e   -> return (This e)
      That    x -> runTheseT (f x)
      These _ x -> do
        t' <- runTheseT (f x)
        return (t >> t')  -- this is where errors get concatenated

Applicative积累ErrorT

免责声明:这种方法更容易适应,因为您已经在m (Either e a)newtype 包装器,但它仅适用于Applicative环境。

如果实际代码只使用Applicative我们可以摆脱的界面ErrorT改变它的Applicative实例。

让我们从非变压器版本开始:

data Accum e a = ALeft e | ARight a

instance Functor (Accum e) where
  fmap f (ARight x) = ARight (f x)
  fmap _ (ALeft e)  = ALeft e

instance Monoid e => Applicative (Accum e) where
  pure = ARight
  ARight f <*> ARight x = ARight (f x)
  ALeft e  <*> ALeft e' = ALeft (e <> e')
  ALeft e  <*> _        = ALeft e
  _        <*> ALeft e  = ALeft e

定义时请注意<*> we know如果双方都是ALefts,因此可以执行<>。如果我们尝试定义相应的Monad我们失败的例子:

instance Monoid e => Monad (Accum e) where
  return = ARight
  ALeft e >>= f = -- we can't apply f

所以唯一的Monad我们可能有的例子是Either。但是之后ap不等于<*>:

Left a <*>  Left b  ≡  Left (a <> b)
Left a `ap` Left b  ≡  Left a

所以我们只能使用Accum as Applicative.

现在我们可以定义Applicative变压器基于Accum:

newtype AccErrorT e m a = AccErrorT {
  runAccErrorT :: m (Accum e a)
}

instance (Functor m) => Functor (AccErrorT e m) where
  fmap f (AccErrorT m) = AccErrorT (fmap (fmap f) m)

instance (Monoid e, Applicative m) => Applicative (AccErrorT e m) where
  pure x = AccErrorT (pure (pure x))
  AccErrorT f <*> AccErrorT x = AccErrorT (liftA2 (<*>) f x)

注意AccErrorT e m本质上是Compose m (Accum e).


EDIT:

AccError被称为AccValidation in validation package.

本文内容由网友自发贡献,版权归原作者所有,本站不承担相应法律责任。如您发现有涉嫌抄袭侵权的内容,请联系:hwhale#tublm.com(使用前将#替换为@)

使用 EitherT 累积错误 的相关文章

  • 将数据类型设置为 Kind * -> * 这不是函子

    布伦特 约尔吉类型分类百科全书 https www haskell org haskellwiki Typeclassopedia给出以下练习 举一个类型的例子 gt 不能将其制成 的实例Functor 不使用undefined 请告诉我什
  • 无点镜头创建不进行类型检查

    在函数中test 我遍历一个列表 从它的成员生成镜头 然后打印一些数据 当我使用有针对性的呼叫风格时 这会起作用 当我使其成为无点时 它无法进行类型检查 为什么会出现这种情况 我该如何解决这个问题 在我看来 GHC 并没有保留排名较高的信息
  • 在 try 中使用零合并运算符? for 抛出并返回可选值的函数

    我想在以下两种情况下使用 nil coalescing 运算符设置默认值 函数抛出错误 函数返回 nil 请看一下下面的代码片段 我有以下问题 为什么 item1 为零 item1和item2的初始化有什么区别 enum VendingMa
  • Go中如何自定义http.Client或http.Transport超时重试?

    我想实现一个自定义http Transport对于标准http Client 如果客户端超时 它将自动重试 附 由于某种原因 习俗http Transport is a 一定有 我已经查过了hashcorp go retryablehttp
  • Haskell 下划线与显式变量

    我已经学习 Haskell 几个星期了 我有一个关于下划线的使用的问题 作为函数参数 我认为用一个具体的例子来问我的问题会更好 假设我想定义一个函数 根据提供的索引提取列表的元素 是的 我意识到 已经是预先定义的 我可以定义该函数的两种方法
  • Haskell scala 互操作性

    我是 Scala 初学者 来自面向对象范式 在了解 Scala 的函数式编程部分时 我被引导到 Haskell 纯函数式编程语言 探索 SO 问题答案 我发现 Java Haskell 具有互操作性 我很想知道 Scala Haskell
  • Haskell:无法预期类型“Integer”与实际类型“Int”

    我已经盯着这段代码有一段时间了 但我无法理解该错误消息 divisors Integer gt Integer divisors n t t lt 1 n mod n t 0 length a gt Integer length 0 len
  • Haskell 中的 print 是纯函数吗?

    Is print在 Haskell 中是纯函数 为什么或者为什么不 我认为不是 因为它并不总是返回与纯函数应返回的值相同的值 类型的值IO Int并不是真正的Int 它更像是一张纸 上面写着 嘿 Haskell 运行时 请生成一个Int如此
  • 当我尝试从列表中删除元素时,如何忽略 ValueError?

    如果我打电话 如何忽略 不在列表中 错误消息a remove x when x不在列表中a 这是我的情况 gt gt gt a range 10 gt gt gt a 0 1 2 3 4 5 6 7 8 9 gt gt gt a remov
  • 规范化且不可变的数据模型

    Haskell如何解决 规范化不可变数据结构 问题 例如 让我们考虑一个表示前女友 男友的数据结构 data Man Man name String exes Woman data Woman Woman name String exes
  • 抑制 R 中的错​​误消息

    我正在 R 中运行模拟研究 有时 我的模拟研究会产生错误消息 当我在函数中实现模拟研究时 当出现此错误消息时模拟停止 我知道抑制错误是不好的做法 但此时对我来说 除了抑制错误然后继续下一个模拟 直到达到我喜欢运行的模拟总数为止 没有其他选择
  • 从远程托管上的 PHP 获取 PHP 错误日志

    是否有 PHP 函数或其他方式以字符串形式获取 PHP 错误日志 我需要这个 因为我无法访问在其他人的服务器上运行的站点的错误日志 他提出通过电子邮件将错误日志发送给我 但这不太方便 有什么方法可以将错误日志输出到 PHP 页面吗 我意识到
  • 如何在 Haskell 中漂亮地打印表格?

    我想在 Haskell 中漂亮地打印一个类似表格的数据结构 列列表 例如 Table StrCol strings a bc c IntCol ints 1 30 2 DblCol doubles 2 0 4 5 3 2 应该渲染类似 st
  • 有没有更好的方法将 UTC 时间转换为大纪元时间?

    我想将文件的修改时间设置为从 exif 数据获取的时间 为了从 exif 获取时间 我发现 Graphics Exif getTag Exif gt String gt IO Maybe String 要设置文件修改时间 我发现 Syste
  • 我该如何实现这个折叠功能呢?

    给出了两种数据类型 颜色 和 植物 data Color Red Pink White Blue Purple Green Yellow deriving Show Eq data Plant Leaf Blossom Color Stal
  • 在 Haskell 中合并两个列表

    无法弄清楚如何合并两个列表通过以下方式在哈斯克尔 INPUT 1 2 3 4 5 11 12 13 14 OUTPUT 1 11 2 12 3 13 4 14 5 我想提出一个更懒的合并版本 merge ys ys merge x xs y
  • Data.Sequence 中的 inits 和 tails 如何工作?

    Louis Wasserman 编写了当前的实现inits and tails in Data Sequence 他表示它们非常高效 事实上 只要查看代码 我就可以看到 无论它们在做什么 它们都是以干净 自上而下的方式进行的 这往往会给惰性
  • ST monad 是如何工作的?

    我知道 ST monad 有点像 IO 的弟弟 而 IO 又是添加了状态 monadRealWorld魔法 我可以想象状态 也可以想象 RealWorld 以某种方式放入 IO 中 但每次我写一个类型签名ST the sST monad 的
  • 如何在Haskell中实现词法分析器和解析器

    我在这里得到了这段代码 它是用Haskell结构的命令式编程语言编写的程序 所以问题是 我如何为这种语言实现词法分析器和解析器 该程序被定义为一系列语句有 6 种类型 goto write stop if goto 和 int int n
  • 我是否需要采取明确的操作来促进与持久数据结构的共享?

    我来自命令式背景 正在尝试实现一个简单的不相交集 并集查找 数据结构 以获得在 Haskell 中创建和修改 持久 数据结构的一些练习 目标是有一个简单的实现 但我也关心效率 我的问题与此相关 首先 我创建了一个按等级并集的不相交集森林实现

随机推荐