3

私は言語のセマンティクスと知っておくべきすべてのことを与えられました。それはいくつかの操作しかサポートせず、データ型の概念はありません。だから私は変数に何でも保存してそれらを操作することができます。

ループと条件、関数呼び出しがあります。それだけです。私はスタートを探しています。理論書ではなく例です。Haskellでそのような基本的な言語インタプリタを実装した人はいますか?ポインタとリファレンスを探しています。

ありがとう !

4

4 に答える 4

6

私は現在、練習プロジェクトとして 1 つに取り組んでいます。

これは動的型付け言語であるため、変数を宣言する必要はありませんが、各値には関連付けられた型があります。Haskell で代数データ型を使用して実装しました。

data Value = BoolValue Bool  -- ^ A Boolean value.
           | NumberValue Double  -- ^ A numeric value.
           | StringValue String  -- ^ A string value.
           -- (several others omitted for simplicity)

プログラムの実行のために、私はStateTErrorTモナド トランスフォーマーを の上に使用していIOます:

-- | A monad representing a step in an RPL program.
--
-- This type is an instance of 'MonadState', so each action is a function that
-- takes an 'RPLContext' as input and produces a (potentially different)
-- 'RPLContext' as its result.  It is also an instance of 'MonadError', so an
-- action may fail (with 'throwRPLError').  And it is built on the 'IO' monad,
-- so 'RPL' computations can interact with the outside world.
type RPL = StateT RPLContext (ErrorT RPLError IO)

-- | Executes an 'RPL' computation.
-- The monadic result value (of type @a@) is discarded, leaving only the final
-- 'RPLContext'.
runRPL :: RPL a  -- ^ The computation to run
       -> RPLContext  -- ^ The computation's initial context
       -> IO (Either RPLError RPLContext)
       -- ^ An 'IO' action that performs the operation, producing either
       -- a modified context if it succeeds, or an error if it fails.
runRPL a = runErrorT . (execStateT a)

「コンテキスト」は、データ スタック (スタックベースの言語) と、現在スコープ内にあるすべての変数を保持する「環境」の組み合わせです。

-- | The monadic state held by an 'RPL' computation.
data RPLContext = RPLContext {
  contextStack :: Stack,  -- ^ The context's data stack.
  contextEnv :: Env  -- ^ The context's environment.
}

Stack(は単なるエイリアスであることに注意してください[Value]。)

その基盤の上に、現在のコンテキスト (モナドのStateT一部によって保持されている) でスタックを操作するなどのことを行うためのさまざまなヘルパー関数があります。RPLたとえば、値をスタックにプッシュする関数は次のとおりです。

-- | Pushes a value onto the stack.
pushValue :: Value -> RPL ()
pushValue x = modifyStack (x:)

-- | Transforms the current stack by a function.
modifyStack :: (Stack -> Stack) -> RPL ()
modifyStack f = do
  stack <- getStack
  putStack $ f stack

-- | Returns the entire current stack.
getStack :: RPL Stack
getStack = fmap contextStack get

-- | Replaces the entire current stack with a new one.
putStack :: Stack -> RPL ()
putStack stack = do
  context <- get
  put $ context { contextStack = stack }

getStackputStack、およびは、 、、および関数modifyStackをモデルにしていますが、レコードMonadStateの1 つのフィールドだけを操作します。getputmodifyRPLContext

言語の組み込みコマンドはすべてモナド内の単なるアクションであり、 のRPLようなツールの上に構築されますpushValue

私の言語でコードを解析するために、私はParsecを使用しています。それはかなりいいです。


私の RPL インタプリタとは関係のない別のトラックで、「 48 時間以内に自分でスキームを書く」が参考になるかもしれません。

于 2012-04-27T05:26:23.180 に答える
6

まず、プログラム全体を EDSL にエンコードします。その EDSL 自体はモナドであり、IO に似ています。GADT を使用すると、これを非常に簡単にエンコードできます。

{-# LANGUAGE GADTs, KindSignatures #-}

module Interp where

import SomeStuff


data Expr :: * -> * where
    -- Commands
    Print   :: String -> Expr ()
    GetLine :: Expr String

    -- Variables (created on demand)
    GetVar :: Name -> Expr Value
    SetVar :: Name -> Value -> Expr ()

    -- Loop constructs
    While :: Expr Bool -> Expr a -> Expr ()
    For   :: Expr a -> Expr Bool -> Expr b -> Expr c -> Expr ()

    -- Expr is a monad
    Return :: a -> Expr a
    Bind   :: Expr a -> (a -> Expr b) -> Expr b

instance Monad Expr where
    return = Return
    (>>=)  = Bind

runExpr :: Expr a -> StateT Variables IO a
runExpr (Print str) = liftIO (putStrLn str)
runExpr GetLine     = liftIO getLine
runExpr (While p x) =
    fix $ \again -> do
        b <- runExpr p
        when b (runExpr x >> again)
runExpr ...

単純な言語の場合、専用の EDSL を使用せずに次のような単純なことを行うこともできます。

parseProgram :: Parser (StateT Variables IO ())
parseProgram = ...

Haskell が関数型プログラミングの概念を結論に導くことを忘れがちです。パーサーがプログラム自体を返すようにします。次に、適切な開始状態で runStateT を実行するだけです。

于 2012-04-27T05:40:47.910 に答える
3

1 つの方法は、インタプリタをStateTモナドで実行し、Mapを使用して可変変数をエミュレートすることです。簡単な例:

import Control.Monad.State
import Data.Map (Map)
import qualified Data.Map as Map

type VarName = String
data Value = VInt Int
           | VString String
type InterpreterState = Map VarName Value

type InterpretM = StateT InterpreterState IO

putVar :: VarName -> Value -> InterpretM ()
putVar varname value = modify (Map.insert varname value)

getVar :: VarName -> InterpretM Value
getVar varname = do
    m <- gets (Map.lookup varname)
    case m of
        Just x  -> return x
        Nothing -> error $ "Variable " ++ varname ++ " is undefined"

インタプリタはInterpretMモナドで実行されます。上記のアクセサーは、変更可能な変数へのアクセスを提供します (クロージャーやレキシカル スコープなどの優れた機能はサポートされていません)。

于 2012-04-27T05:17:37.327 に答える
1

ここにいくつかのリソースがあります https://github.com/budabudimir/imp_interpreter、これはここで説明されている単純な命令型言語のインタープリターですhttp://fsl.cs.illinois.edu/images/0/0d/CS522-Spring-2011-PL -book-imp.pdf

于 2015-03-22T11:03:33.000 に答える