Haskellでは、中置演算子を自由に定義することができ、多くの中置演算子を活用してプログラムを書きます。
module Main where
(<=>) :: Ord a => a -> a -> Ordering
a <=> b = compare a b
abs' :: Int -> Int
abs' x = case x <=> 0 of
LT -> -x
_ -> x
answer :: Double
answer = 2 + 4 * 2 * 10 / 2
main :: IO ()
main = do
print . abs' . read =<< getLine
print answer
-- このmainはすこしやりすぎ
GHCは、すべての中置演算子を左結合と仮定して構文解析を行います。
その後、Renamerと呼ばれる層でinfix宣言に基づいた構文木の書き換えを行うことで、構文解析器の魔境化を防いでいます。
この処理について、一連の流れをまとめました。
構文解析
-ddump-parsed
オプションを付けてコンパイルすると、以下のような出力を得られます。
==================== Parser ====================
module Main where
(<=>) :: Ord a => a -> a -> Ordering
a <=> b = compare a b
abs' :: Int -> Int
abs' x
= case x <=> 0 of {
LT -> - x
_ -> x }
answer :: Double
answer = 2 + 4 * 2 * 10 / 2
main :: IO ()
main
= do { print . abs' . read =<< getLine;
print answer }
この出力からは中置演算子を含む式がどのようなASTになっているかがわかりませんが、
https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/Parser によると、
Infix operators are parsed as if they were all left-associative. The renamer uses the fixity declarations to re-associate the syntax tree.
実際にcompiler/parser/Parser.yを見てみると、
infixexp :: { LHsExpr GhcPs }
: exp10 { $1 }
| infixexp qop exp10 {% ams (sLL $1 $> (OpApp $1 $2 placeHolderFixity $3))
[mj AnnVal $2] }
となっており、たしかに頭から左結合でASTを構築しているようです。
## Renamer
`-ddump-rn`オプションを付けてコンパイルすると、以下の出力が得られます。
```hs
==================== Renamer ====================
(Main.<=>) :: Ord a_aRh => a_aRh -> a_aRh -> Ordering
a_a1S3 Main.<=> b_a1S4 = compare a_a1S3 b_a1S4
Main.abs' :: Int -> Int
Main.abs' x_a1S5
= case x_a1S5 Main.<=> 0 of
LT -> - x_a1S5
_ -> x_a1S5
Main.answer :: Double
Main.answer = 2 + 4 * 2 * 10 / 2
Main.main :: IO ()
Main.main
= do print . Main.abs' . read =<< getLine
print Main.answer
見ての通り、renamerは識別子がどのモジュールに属すのかを解決し、ローカル変数にユニークな名前を付け直します。
この他にも、renamerは次のような処理を行います。
- 中置演算子を含む式のASTを正しい形へ組み替え
- 相互再帰関数の識別
- スコープ外参照、未使用の宣言、未使用のimport、重複したパターンの検出
-ddump-rn-trace
オプションで挙動を確認すると、
...
addUsedGRE
+ parent:Num
imported from ‘Prelude’ at Main.hs:1:8-11
(and originally defined in ‘GHC.Num’)
lookupFixityRn_either:
looking up name in iface and found: +
infixl 6
addUsedGRE
* parent:Num
imported from ‘Prelude’ at Main.hs:1:8-11
(and originally defined in ‘GHC.Num’)
lookupFixityRn_either:
looking up name in iface and found: *
infixl 7
addUsedGRE
* parent:Num
imported from ‘Prelude’ at Main.hs:1:8-11
(and originally defined in ‘GHC.Num’)
lookupFixityRn_either:
looking up name in iface and found: *
infixl 7
addUsedGRE
/ parent:Fractional
imported from ‘Prelude’ at Main.hs:1:8-11
(and originally defined in ‘GHC.Real’)
lookupFixityRn_either:
looking up name in iface and found: /
infixl 7
...
確かに優先順位を検索しているようです。
実際にrenamerの処理の本体であるRnExpr.rnExpr
のソース(compiler/rename/RnExpr.hs)を見てみると、
rnExpr (OpApp e1 op _ e2)
= do { (e1', fv_e1) <- rnLExpr e1
; (e2', fv_e2) <- rnLExpr e2
; (op', fv_op) <- rnLExpr op
-- Deal with fixity
-- When renaming code synthesised from "deriving" declarations
-- we used to avoid fixity stuff, but we can't easily tell any
-- more, so I've removed the test. Adding HsPars in TcGenDeriv
-- should prevent bad things happening.
; fixity <- case op' of
L _ (HsVar (L _ n)) -> lookupFixityRn n
L _ (HsRecFld f) -> lookupFieldFixityRn f
_ -> return (Fixity NoSourceText minPrecedence InfixL)
-- c.f. lookupFixity for unbound
; final_e <- mkOpAppRn e1' op' fixity e2'
; return (final_e, fv_e1 `plusFV` fv_op `plusFV` fv_e2) }
最後から二行目で呼ばれている`mkOpAppRn`は[compiler/rename/RnTypes.hs](https://ghc.haskell.org/trac/ghc/browser/ghc/compiler/rename/RnTypes.hs)に存在します。
> ```hs
mkOpAppRn :: LHsExpr GhcRn -- Left operand; already rearranged
-> LHsExpr GhcRn -> Fixity -- Operator and fixity
-> LHsExpr GhcRn -- Right operand (not an OpApp, but might
-- be a NegApp)
-> RnM (HsExpr GhcRn)
>
-- (e11 `op1` e12) `op2` e2
mkOpAppRn e1@(L _ (OpApp e11 op1 fix1 e12)) op2 fix2 e2
| nofix_error
= do precParseErr (get_op op1,fix1) (get_op op2,fix2)
return (OpApp e1 op2 fix2 e2)
>
| associate_right = do
new_e <- mkOpAppRn e12 op2 fix2 e2
return (OpApp e11 op1 fix1 (L loc' new_e))
where
loc'= combineLocs e12 e2
(nofix_error, associate_right) = compareFixity fix1 fix2
>
---------------------------
-- (- neg_arg) `op` e2
mkOpAppRn e1@(L _ (NegApp neg_arg neg_name)) op2 fix2 e2
| nofix_error
= do precParseErr (NegateOp,negateFixity) (get_op op2,fix2)
return (OpApp e1 op2 fix2 e2)
>
| associate_right
= do new_e <- mkOpAppRn neg_arg op2 fix2 e2
return (NegApp (L loc' new_e) neg_name)
where
loc' = combineLocs neg_arg e2
(nofix_error, associate_right) = compareFixity negateFixity fix2
>
---------------------------
-- e1 `op` - neg_arg
mkOpAppRn e1 op1 fix1 e2@(L _ (NegApp _ _)) -- NegApp can occur on the right
| not associate_right -- We *want* right association
= do precParseErr (get_op op1, fix1) (NegateOp, negateFixity)
return (OpApp e1 op1 fix1 e2)
where
(_, associate_right) = compareFixity fix1 negateFixity
>
---------------------------
-- Default case
mkOpAppRn e1 op fix e2 -- Default case, no rearrangment
= ASSERT2( right_op_ok fix (unLoc e2),
ppr e1 $$ text "---" $$ ppr op $$ text "---" $$ ppr fix $$ text "---" $$ ppr e2
)
return (OpApp e1 op fix e2)
なんだか単項の-
演算子の処理に少し涙ぐましい努力が見られますが、ここで中置演算子を含む式のASTの変換が行われているのがわかります。
まとめ
GHCにおける中置演算子の処理についてまとめました。
GHCは内部仕様のドキュメントが整っているので、コードリーディングなどにおすすめです。
参考文献など
-
The GHC Commentary
- Compiling one module: HscMain コンパイルパスの俯瞰
- The Parser 構文解析器とGHCのフロントエンドにおける戦略
- The renamer 名前解決を含むもろもろの意味検査
- GHCのソースコード(Githubのミラー)
- Haskell GHC開発に関する情報源いろいろ