module IR where import Debug.Trace import Spec import ASTData data IRType = IRSimpleType (DType ()) | IRGenericsType String [IRType] -- vector などのつもり | IRUserType String [IRType] -- Pair, Tuple, Recordたち | IRVoidType deriving (Eq, Show) -- type IRType = DType () type IRNameAndType = (String, IRType) -- Emoto 2018/01/16: added the origianl state ID type IRNameAndTypeWithId = (IRNameAndType, Int) type IRVertexComputeState = (Int, Int) -- Phase number and Step number -- 全体 data IRProg = IRProg String -- プログラム名 [IRTypeDecl] -- 各フェーズが使うデータ型 IRVertexStruct -- 頂点のデータ型 IREdgeStruct -- 枝の値のデータ型 IRMsgStruct -- メッセージのデータ型 IRAggStruct -- Aggregator のデータ型 Bool -- 逆向き辺を使えば True そうでなければ False [String] -- message names to put message tag OptimizeInfo -- optimization information [IRConstant] -- 定数 IRPhaseCompute -- Vertex.compute() / Master.compute() を生成 IRVertexComputeState -- 初期状態 [IRMethod] -- 他のメソッド deriving (Eq, Show) ------------------------------------------------------------------------ -- 型定義関係 ------------------------------------------------------------------------ -- データ型定義 data IRTypeDecl = IRTypeDecl String -- 構造体名 [IRNameAndType] -- 構造体メンバー (名前,型) deriving (Eq, Show) -- 頂点のデータ型 data IRVertexStruct = IRVertexStruct String -- "NData_??" String -- フェーズ番号 String -- ステップ番号 -- Emoto 2018/01/16: modified to add the origianl pahse ids for fields [IRNameAndTypeWithId] -- 構造体メンバー (名前,型) : Prev/Curr 付きのもの [IRNameAndTypeWithId] -- 構造体メンバー (名前,型) : val + Prev/Curr なしでよいもの deriving (Eq, Show) -- 枝の値のデータ型 data IREdgeStruct = IREdgeStruct String -- "EdgeData_??" [IRNameAndType] -- 構造体メンバー (名前,型) deriving (Eq, Show) -- 頂点間メッセージのデータ型 -- data IRMsgStruct = IRMsgStruct [IRNameAndType] -- 構造体メンバー (名前,型) -- deriving (Eq, Show) data IRMsgStruct = IRMsgStruct String -- MsgData_?? [IRNameAndType] -- 構造体メンバー (名前,型) deriving (Eq, Show) -- 備考 -- [("m1", int), ("m2", double)] -- sendToNeighbor(("m1", ival)); -- sendToNeighbor(("m2", dval)); -- class MsgData extends Writable { -- int mtype; -- IntWritable m1; -- DoubleWritable m2; -- serialize() { -- if (mtype == 1) { new IntWritable(1).serim1.serialize(); m1.serialize(); } -- } -- Aggregate するデータ -- data IRAggStruct = IRAggStruct [(IRNameAndType, -- それぞれの名前と型 -- IRAggOp)] -- 用いる演算 -- deriving (Eq, Show) data IRAggStruct = IRAggStruct String -- AggData_?? [(IRNameAndType, -- それぞれの名前と型 IRAggOp)] -- 用いる演算 deriving (Eq, Show) -- 定数 data IRConstant = IRConstant IRNameAndType -- 型と名前 IRExpr -- 式 deriving (Eq, Show) getIRConstantVar (IRConstant v e) = v getIRConstantExp (IRConstant v e) = e ------------------------------------------------------------------------ -- メソッド定義 ------------------------------------------------------------------------ data IRMethod = IRMethod IRType -- 返り値の型 String -- メソッド名 [IRNameAndType] -- 引数の名前と型 IRBlock -- 本体 deriving (Eq, Show) data IRPhaseCompute = IRPhaseCompute [IRPhaseComputeProcess] -- 各 (phase,step) における処理内容 deriving (Eq, Show) data IRPhaseComputeProcess = IRPhaseComputeProcess IRVertexComputeState -- Phase 番号,Step 番号 Bool -- termination condition == Fix? [IRNameAndType] -- 必要な局所変数 IRBlock -- 本体 (含む受信処理) [(IRExpr, IRVertexComputeState, IRBlock)] -- 遷移条件,(Phase, Step), 通信 deriving (Eq, Show) data IRBlock = IRBlock [IRNameAndType] -- 局所変数 [IRStatement] -- 本体 deriving (Eq, Show) data IRStatement = IRStatementLocal IRVar IRExpr -- ローカルな計算による値の変数への代入 | IRStatementMsg IRVar IRAggOp IRExpr -- 隣接頂点の値の集約 | IRStatementReturn IRExpr -- return文 | IRStatementVTH -- voteToHalt | IRStatementAggr IRNameAndType IRExpr [IRExpr] -- Aggregator への書き込み | IRStatementSendN IRNameAndType IRExpr [IRExpr] -- (通常の辺に沿った) 送信メッセージのメンバーの名前/型と値 | IRStatementSendR IRNameAndType IRExpr [IRExpr] -- (辺を逆行する) 送信メッセージのメンバーの名前/型と値 | IRStatementIfThen IRExpr IRBlock deriving (Eq, Show) -- IRStatementMsg "v.foo" min (mval + 1) -- このくらいの情報から次のコードを出したい -- int foo = Integer.MAX_VALUE; -- for (IntWritable msg : messages) { -- foo = Math.min(foo, msg.getValue()); -- } -- v.foo = new IntWritable(foo); data IRVar = IRVarLocal IRNameAndType -- 局所変数 -- | IRVarVertex IRNameAndType -- 頂点のメンバー | IRVarVertex IRNameAndType IRPrevCurr [IRNameAndType] -- 頂点のメンバー | IRVarEdge IRNameAndType [IRNameAndType] -- 枝の値,フィールドアクセス | IRVarAggr IRNameAndType -- Aggregator deriving (Eq, Show) data IRPrevCurr = IRPrev -- prev | IRCurr -- curr | IRNone deriving (Eq, Show) data IRExpr = IRIf IRExpr IRExpr IRExpr | IRFunAp IRFun [IRExpr] | IRVExp IRVar | IRMVal IRNameAndType -- 送信メッセージ用 | IRCExp IRType IRConst | IRAggr IRNameAndType deriving (Show, Eq) data IRFun = IRFun String | IRBinOp String deriving (Show, Eq) data IRAggOp = IRAggMin | IRAggMax | IRAggSum | IRAggProd | IRAggAnd | IRAggOr | IRAggChoice IRConst -- used? | IRTupledAgg [IRAggOp] -- for internal use? deriving (Show, Eq) data IRConst = IRCInt Int | IRCBool Bool | IRCString String | IRCDouble Double deriving (Eq, Show)