我可以在运行时从Haskell程序中反映消息吗



我正在编写一个程序,根据许多复杂的规则验证复杂的数据结构。它输入数据并输出指示数据问题的消息列表。

按照以下思路思考:

import Control.Monad (when)
import Control.Monad.Writer (Writer, tell)
data Name = FullName String String | NickName String
data Person = Person { name :: Name, age :: Maybe Int }
data Severity = E | W | C   -- error/warning/comment
data Message = Message { severity :: Severity, code :: Int, title :: String }
type Validator = Writer [Message]
report :: Severity -> Int -> String -> Validator ()
report s c d = tell [Message s c d]
checkPerson :: Person -> Validator ()
checkPerson person = do
  case age person of
    Nothing -> return ()
    Just years -> do
      when (years < 0) $ report E 1001 "negative age"
      when (years > 200) $ report W 1002 "age too large"
  case name person of
    FullName firstName lastName -> do
      when (null firstName) $ report E 1003 "empty first name"
    NickName nick -> do
      when (null nick) $ report E 1004 "empty nickname"

对于文档,我还想编译一个该程序可以输出的所有消息的列表。也就是说,我想要获得的值:

[ Message E 1001 "negative age"
, Message W 1002 "age too large"
, Message E 1003 "empty first name"
, Message E 1004 "empty nickname"
]

我可以将消息从checkPerson移到一些外部数据结构中,但我喜欢在使用消息的地方定义消息。

我可以(也可能应该)在编译时从AST中提取消息。

但Haskell的灵活性让我思考:我能在运行时实现?也就是说,我可以写一个函数吗

allMessages :: (Person -> Validator ()) -> [Message]

这样CCD_ 2会给我上面的列表?

当然,checkPersonValidator不必保持不变。

我几乎可以(不完全)看到如何制作一个带有"后门"的自定义Validator monad,它将以某种"反射模式"运行checkPerson,遍历所有路径并返回遇到的所有Message。我必须编写一个自定义when函数,它知道在某些情况下(哪些情况?)忽略它的第一个参数。所以,一种DSL。也许我甚至可以模仿模式匹配?

那么:我能做这样的事情吗?我该如何做?我该牺牲什么?

请随时提出任何解决方案,即使它们不完全符合上述描述。

这种半静态分析基本上正是箭头的发明目的。所以让我们做一支箭!我们的箭头基本上只是一个Writer动作,但它能记住它在任何给定时刻可能发出的信息。首先,一些样板:

{-# LANGUAGE Arrows #-}
import Control.Arrow
import Control.Category
import Control.Monad.Writer
import Prelude hiding (id, (.))

现在,上面描述的类型:

data Validator m a b = Validator
    { possibleMessages :: [m]
    , action :: Kleisli (Writer m) a b
    }
runValidator :: Validator m a b -> a -> Writer m b
runValidator = runKleisli . action

有一些简单的例子需要落实。特别感兴趣的是:两个验证器的组合会记住来自第一个动作和第二个动作的消息。

instance Monoid m => Category (Validator m) where
    id = Validator [] id
    Validator ms act . Validator ms' act' = Validator (ms ++ ms') (act . act')
instance Monoid m => Arrow (Validator m) where
    arr f = Validator [] (arr f)
    first (Validator ms act) = Validator ms (first act)
instance Monoid m => ArrowChoice (Validator m) where
    left (Validator ms act) = Validator ms (left act)

所有的魔法都在操作中,它实际上可以让你报告一些事情:

reportWhen :: Monoid m => m -> (a -> Bool) -> Validator m a ()
reportWhen m f = Validator [m] (Kleisli $ a -> when (f a) (tell m))

这是一个操作,当你准备输出一条可能的消息时,它会注意到并记下它。让我们复制你的类型,并展示如何将checkPerson编码为箭头。我已经稍微简化了您的消息,但没有什么重要的不同——只是在示例中减少了语法开销。

type Message = String
data Name = FullName String String | NickName String -- http://www.kalzumeus.com/2010/06/17/falsehoods-programmers-believe-about-names/
data Person = Person { name :: Name, age :: Maybe Int }
checkPerson :: Validator Message Person ()
checkPerson = proc person -> do
    case age person of
        Nothing -> returnA -< ()
        Just years -> do
            "negative age"  `reportWhen` (<  0) -< years
            "age too large" `reportWhen` (>200) -< years
    case name person of
        FullName firstName lastName -> do
            "empty first name" `reportWhen` null -< firstName
        NickName nick -> do
            "empty nickname"   `reportWhen` null -< nick

我希望你会同意,这个语法与你最初写的内容相差不远。让我们看看它在ghci:中的作用

> runWriter (runValidator checkPerson (Person (NickName "") Nothing))
((),"empty nickname")
> possibleMessages checkPerson 
["empty nickname","empty first name","age too large","negative age"]

相关内容

  • 没有找到相关文章