我正在尝试构建一个抽象语法树,允许使用monad do
表示法进行定义,如下所示:
ast = do
Variable uint8 "i"
Function Void "f" $ do
Variable uint8 "local_y"
Comment "etc. etc."
我在这里展示的构造是从Text.Blaze.Html收集的,用于定义HTML树。
问题分散在以下各个方面。主要问题是如何正确地做到这一点。当然,非常感谢任何有助于理解这种结构的输入。
所以,首先,这是一个小的,有缺陷的,但“有效”的例子。它是一个语法树,包含某些类型的变量和函数的声明,注释行以及用于替换的占位符声明:
{-# LANGUAGE ExistentialQuantification #-}
module Question
where
import Control.Applicative
import Data.Monoid (Monoid, (<>))
import Data.String.Utils (rstrip)
type NumberOfBits = Word
type VariableName = String
data Type = UInt NumberOfBits
| Int NumberOfBits
| Void
uint8 = UInt 8
int8 = Int 8
instance Show Type where
show (UInt w) = "uint" <> show w
show (Int w) = "int" <> show w
show Void = "void"
data TreeM a = Variable Type VariableName -- variable declaration
| Function Type VariableName (TreeM a) -- function declaration
| Comment String -- a comment
| PlaceHolder String -- a placeholder with
| forall b. Append (TreeM b) (TreeM a) -- combiner
| Empty a -- needed for what?
type Tree = TreeM ()
subTreeOf :: TreeM a -> a
subTreeOf (Variable _ _) = undefined
subTreeOf (Function _ _ t) = subTreeOf t
subTreeOf (Comment _) = undefined
subTreeOf (Empty t) = t
instance Monoid a => Monoid (TreeM a) where
mempty = Empty mempty
mappend = Append
mconcat = foldr Append mempty
instance Functor TreeM where
fmap f x = x `Append` (Empty (f (subTreeOf x))) -- fmap :: (a -> b) -> f a -> f b
instance Applicative TreeM where
pure x = Empty x
(<*>) x y = (x `Append` y) `Append` (Empty (subTreeOf x (subTreeOf y))) -- (<*>) :: f (a -> b) -> f a -> f b
(*>) = Append
instance Monad TreeM where
return x = Empty x
(>>) = Append -- not really needed: (>>) would default to (*>)
t >>= f = t `Append` (f (subTreeOf t))
indent :: String -> String
indent s = rstrip $ unlines $ map (" "<>) (lines s)
render :: TreeM a -> String
render (Variable y n) = "Variable " <> (show y) <> " " <> show n
render (Function r n t) = "Function" <> " " <> n <> " returning " <> (show r) <> ":\n" <> indent (render t)
render (PlaceHolder n) = "Placeholder \"" <> n <> "\""
render (Append t t') = (render t) <> "\n" <> (render t')
render (Empty _) = ""
-- |In input tree t substitute a PlaceHolder of name n' with the Tree t'
sub :: TreeM a -> (String, TreeM a) -> TreeM a
sub t@(PlaceHolder n) (n', t') = if n == n' then t' else t
sub (Function y n t) s = Function y n (sub t s)
--sub (Append t t') s = Append (sub t s) (sub t' s) -- Error!
sub t _ = t
code :: Tree
code = do
Variable uint8 "i"
Variable int8 "j"
Function Void "f" $ do
Comment "my function f"
Variable int8 "i1"
Variable int8 "i2"
PlaceHolder "the_rest"
main :: IO ()
main = do
putStrLn $ render code
putStrLn "\nNow apply substitution:\n"
putStrLn $ render (sub code ("the_rest", Comment "There is nothing here"))
这是(应该)定义复杂树结构的一种非常简洁的方法。特别是,这应该是语法上最不嘈杂,用户友好的定义语法树的方法。
总的来说,我很难理解a
中TreeM a
的确切含义。我认为a
的方式可以是Variable
,Function
,PlaceHolder
等任何类型。
我注意到一些令我感到奇怪的事情:
forall b. Append (TreeM b) (TreeM a)
中TreeM a
的{{1}}和TreeM b
参数的顺序似乎相反。无论如何,在和类型中使用存在量词看起来很奇怪。如果我理解正确,它会为Append
定义一系列构造函数。TreeM
,Functor
和Applicative
所需的所有功能中,实际使用的唯一功能是monad Monad
。 (这表明一个免费的monad可能是这项工作的正确工具。)实际上,我从未想过这样的符号使用>>
运算符,并且可以使用这个事实。 >>
中使用undefined
才能使该功能合计。如上所述,上面的例子是有缺陷的:构造的某些部分不适合AST:
subTreeOf
的定义对HTML树有意义,它用于Empty
之类的空标签。但是对于AST来说没有任何意义。保持<br />
和Applicative
实施工作正常。Functor
和Functor
的实现可能对HTML树有意义,但不适用于AST。即使对于HTML,我也不太了解Applicative
和applicative fmap
的用途。两者都通过按下节点并添加<*>
类型来扩展树。我不太清楚HTML树上的自然转换代表什么。我很惊讶应用Empty
定义中的subTreeOf x (subTreeOf y)
实际上是正确的语法,还是隐含的<*>
?
在AST上应用转换是很自然的。 >>
用作应用转换的小玩具。此处仅具有部分实现的函数PlaceHolder
应该用占位符“the_rest”替换注释。必要
sub
无法编译,sub (Append t t') s = Append (sub t s) (sub t' s)
的预期类型为s
,实际类型为(String, TreeM b)
。
将类型更改为
另一方面,(String, TreeM a)
违反了sub :: TreeM a -> (String, TreeM b) -> TreeM a
的定义,现在我被卡住了。
事实上,这个sub p@(PlaceHolder n)
究竟是什么sub
对于AST应该是什么?
当讨论AST的monad时,“free monad”这个词会经常出现。但是免费monad依赖fmap
Functor
进行自由构建,此处显示的fmap
不适合AST。一旦确定了正确的fmap
,免费的monad应该做其余的事 - 也许。
fmap
似乎正确的fmap
是成功的关键,正确的fmap
可能会变得更加明显。
循环可以用<*>
编写,这是建立AST重复部分的好方法:
forM_
条件部分可以使用forM_ ["you", "get", "the", "idea"] $ \varName -> do
Variable uint8 varName
,when
等。
unless
语义分析,例如确保正确的申报顺序,也可以如第一个答案所指出的那样。
视觉线索:我喜欢的另一件事是,在上面显示的构造中,控制结构如if-then-else,when hasCppDestructor $ do
Comment "We need the destructor"
Function NoReturnType "~SomeClass" $ do
...
等开始小写,而AST行开始大写。
关于这个方向的几句话,可能是:这个想法是使用一个足够好的嵌入式DSL,它允许自动定义一个AST,它相当抽象地代表一个需要用C,C ++实现的复杂FSM。 ,Python,Java,Go,Rust,Javascript,等等......上面的forM_
函数将可证明正确的AST映射到目标语言。
render
不会默认为>>
,而是默认为*>
!答案 0 :(得分:2)
我不确定这整个方法是不是一个好主意(尽管我实际上已经多次尝试过类似的事情)。
请注意,Blaze.MarkupM
,HaTeX.LaTeXM
等monad并非真正的monad。他们真的只是 monoids 想要访问monadic组合器(主要是滥用do
符号,但它也允许堆叠monad变换器在顶部,这可能有点意义) 。也就是说,他们只是专门的Writer
monad!当前,你真的在做同样的事情;如果那是你想要的,那么最好的方法就是将你的类型设计为Monoid Tree
,然后看看Writer Tree
monad的结构并且,如果需要,将其重构为TreeM
数据结构。 (HaTeX没有做到这一点,但只保留LaTeX
和LaTeXM
单独的类型,只有一个共同的类接口,这可以说是一种更清晰的方法,尽管它可能不是最佳的性能。)
结果将与Blaze.MarkupM
/您现在拥有的结构非常相似。我可以讨论你的个别问题,但实际上,他们都可以通过查看类型与作家monad同构的方式来回答。
实际上,您根本不需要Monad
个实例来使用do
,因此:
Prelude> 2 * do 1 + 1
4
因此,如果您只是想滥用do
以避免在树形布局中使用括号,但实际上并没有一种明智的方法来隐藏结构中的可绑定变量,请考虑 not 编写任何monad实例。只有具有多行的do
块才需要该实例,但如果这些行中没有一行绑定任何变量,那么您始终只需将隐式>>
替换为显式{ {1}},例如
<>
唯一的问题是:这些行不能包含 Function Void "f" $ do
Variable uint8 "local_y"
<> Comment "etc. etc."
运算符,因为它的优先级低于$
。绕过这个的一个好方法是观察<>
,所以你可以把你的例子写成
($) = id
这是否比定义一个不太多的monad实例更加滥用语法是值得商榷的。 IMO,如果你定义了这样一个monad实例,你应该立即使它成为 monad转换器,就像ast = do
Variable uint8 "i"
<> Function Void "f" `id`do
Variable uint8 "local_y"
<> Comment "etc. etc."
那样,因为这也允许包含HaTeX
个动作的选项你的AST构建(例如,硬包含外部源文件)。
所有这一切:对于你的应用程序来说,让一个IO
实例 只是一个“加糖的幺半群”但实际上是绑定的,实际上是有意义的。 ,变量以有用的方式。这个功能不适用于Monad
,但肯定适用于像AST这样的C ++ / Python / JavaScript语言,它可能非常有用,因为它确保在使用之前定义变量,就在Haskell语法中。而不是你的例子,你写
blaze
变量将在引擎盖下然后实际上只是编号标识符,根据状态变量选择。
实施大致如下:
ast = do
i <- variable uint8
Function Void "f" $ do
local_y <- variable uint8
Comment "etc. etc."
答案 1 :(得分:0)
我对AST Append
编码采用的路径似乎是一个死胡同,所以我深入研究了自由monad。结果如下:
free monad非常适合此类问题。免费monad允许将程序的“逻辑”与其效果分开。 ASTs属于这种模式。在这个例子中,'逻辑'是AST,效果只是相当印刷。
更一般地说,'效果'可能意味着分析,测试(例如干运行),运行校样,漂亮打印,压缩......,当然还有实际执行。
有很多关于免费monad的文章,这里有一些有用的资源可以开始:
现在,使用Control.Monad.Free
解决方案将如下所示:
{-# LANGUAGE DeriveFunctor #-}
module Main where
import Control.Monad.Free
import Data.Monoid ((<>))
import Data.String.Utils (rstrip)
type NumberOfBits = Word
type VariableName = String
data Type = UInt NumberOfBits
| Int NumberOfBits
| Void
deriving Eq
uint8 = UInt 8
int8 = Int 8
instance Show Type where
show (UInt w) = "uint" <> show w
show (Int w) = "int" <> show w
show Void = "void"
data AST n = Variable Type VariableName n -- variable declaration
| Function Type VariableName (Free AST ()) n -- function declaration
| Comment String n -- a comment
| PlaceHolder String n -- a placeholder with @name holds holds more code
| End
deriving (Eq, Show, Functor)
end :: Free AST ()
end = liftF End -- is exactly Pure ()
variable :: Type -> VariableName -> Free AST ()
variable y n = liftF (Variable y n ())
function :: Type -> VariableName -> Free AST () -> Free AST ()
function t n p = liftF (Function t n p ())
placeHolder :: String -> Free AST ()
placeHolder n = liftF (PlaceHolder n ())
comment :: String -> Free AST ()
comment c = liftF (Comment c ())
indent :: String -> String
indent s = rstrip $ unlines $ map (" "<>) (lines s)
render :: Free AST r -> String
render (Free (Variable y n next)) = "Variable " <> show y <> " " <> show n <> "\n" <> render next
render (Free (Function t n f next)) = "Function \"" <> n <> "\" returning " <> show t <> ":\n"
<> indent (render f) <> "\n" <> render next
render (Free (Comment c next)) = "// " <> c <> "\n" <> render next
render (Free (PlaceHolder s next)) = "PlaceHolder \"" <> s <> "\"\n" <> render next
render (Free End) = "end"
render (Pure r) = "return\n"
code :: Free AST ()
code = do
placeHolder "includefiles"
variable uint8 "i"
variable int8 "j"
function Void "f" $ do
comment "This is a function!"
variable (Int 8) "local_i"
sub :: AST (Free AST b) -> Free AST b
sub (Variable t n next) = do
variable t n
next
sub (Function t n f next) = do
function t n f
next
sub (Comment c next) = do
comment c
next
sub (PlaceHolder s next) = do
comment "placeholder"
next
main :: IO ()
main = do
putStrLn $ render code
putStrLn "-- Apply subst\n"
putStrLn $ render (iterM sub code)
并非所有这些都需要如此明确地拼写出来。可以使用Control.Monad.Free.TH
删除部分样板。
Control.Monad.Free
是规范实现,但链式数据结构意味着某些操作的二次复杂性。作者本人Ed Kmett在Control.Monad.Free.Church
中解决了这个问题,其中使用了不同的编码。请参阅free monad benchmark了解其他免费monad实现的基准和指针。
超越免费monad,cofree monads正式化了解释器及其与“逻辑”的关系。例如,请参阅David Laing撰写的"Free for DSLs, cofree for interpreters"。