9

最近、Web で関数型プログラミングについて少し読んでいて、その背後にある概念についての基本的な考え方を理解できたと思います。

ある種の状態を含む日常的なプログラミングの問題が、純粋な関数型プログラミング言語でどのように解決されるのか興味があります。

たとえば、「C プログラミング言語」という本の単語カウント プログラムを純粋な関数型言語で実装するにはどうすればよいでしょうか。

ソリューションが純粋に機能的なスタイルである限り、あらゆる貢献を歓迎します。

本のワードカウントCコードは次のとおりです。

#include <stdio.h>

#define IN  1 /* inside a word */
#define OUT 0 /* outside a word */

/* count lines, words, and characters in input */
main()
{
  int c, nl, nw, nc, state;

  state = OUT;
  nl = nw = nc = 0;
  while ((c = getchar()) != EOF) {
    ++nc;
    if (c == '\n')
      ++nl;
    if (c == ' ' || c == '\n' || c = '\t')
      state = OUT;
    else if (state == OUT) {
      state = IN;
      ++nw;
    }
  }

  printf("%d %d %d\n", nl, nw, nc);
}
4

11 に答える 11

9

基本的に、機能的なスタイルでは、データのストリームを取得する IO 操作を、現在のキャラクターと現在の状態に基づいたステートフル トランジションの純粋な操作から分割する必要があります。

Tikhon の Haskell ソリューションは非常にクリーンですが、入力データに対して 3 つのパスを実行するため、結果が計算されるまで入力全体がメモリに格納されます。データを段階的に処理することができます。これは以下で Text パッケージを使用して行いますが、他の高度な Haskell ツールは使用しません (これにより、非 Haskeller による理解が犠牲になる可能性があります)。

まず、プリアンブルがあります。

{-# LANGUAGE BangPatterns #-}

import Data.Text.Lazy as T
import Data.Text.Lazy.IO as TIO

次に、プロセスの状態を保持するデータ構造を定義します (状態 IN/OUT と共に文字数、単語数、行数)。

data Counts = Cnt { nc, nl, nw :: !Int
                  , state :: State  }
        deriving (Eq, Ord, Show)

data State = IN | OUT
        deriving (Eq, Ord, Show)

ここで、簡単に使用できるように「ゼロ」状態を定義します。通常、多くのヘルパー関数を作成するか、 lense のようなパッケージを使用して、Counts構造内の各フィールドを簡単にインクリメントしますが、この答えは省略します:

zeros :: Counts
zeros = Cnt 0 0 0 OUT

それでは、一連の if/else ステートメントを純粋なステート マシンに変換します。

op :: Counts -> Char -> Counts
op c '\n' = c { nc = nc c + 1, nw = nw c + 1, nl = nl c + 1, state=OUT }
op c ch | ch == ' ' || ch == '\t' = c { nc = nc c + 1, state=OUT }
        | state c == OUT = c { nc = nc c + 1, nw = nw c + 1, state = IN }
        | otherwise  = c { nc = nc c + 1 }

最後に、main関数は入力ストリームを取得し、操作を文字に重ねます。

main = do
        contents <- TIO.getContents
        print $ T.foldl' op zeros contents

編集:あなたは構文を理解していないと述べました。ここで説明するさらに単純なバージョンを次に示します。

import Data.Text.Lazy as T
import Data.Text.Lazy.IO as TIO

op (nc, nw, nl, st) ch
  | ch == '\n'              = (nc + 1, nw + 1 , nl + 1, True)
  | ch == ' ' || ch == '\t' = (nc + 1, nw     , nl    , True)
  | st                      = (nc + 1, nw + 1 , nl    , False)
  | otherwise               = (nc + 1, nw     , nl    , st)

main = do
        contents <- TIO.getContents
        print $ T.foldl' op (0,0,0,True) contents
  • ステートメントは、使用するおよび関数へのimportアクセスを提供します。getContentsfoldl'

  • この関数は、基本的に C の if/elseif/else シリーズに似た一連opのガード (次のようなパーツ) を使用します。| ch = '\n'

  • タプル( ... , ... , ... , ... )にはすべての状態が含まれています。Haskell 変数は不変であるため、前の変数の値に 1 を追加する (または追加しない) ことで、新しいタプルを作成します。

于 2012-04-07T06:35:26.837 に答える
6

これを行う簡単な方法は、入力を読み取り、いくつかの簡単な関数を使用して行/単語/文字数を取得することです。次のようなものが機能します。

count :: String -> (Int, Int, Int)
count str = (length $ lines str, length $ words str, length str)

main :: IO ()
main = fmap count getContents >>= print

これはまったく同じではありませんが、近いものです。

これは本当に簡単に機能します。文字列を指定すると、標準関数を使用して行のリストに変換し、標準lines関数を使用して単語のリストに変換できwordsます。Stringは だけなので、文字数を返します[Char]lengthこれが、3 つのカウントを取得する方法です。(参考までに、length $ lines strは と同じlength (lines str)です。)

重要なアイデアはIO、入力の読み取りと出力を実際のロジックから分離する方法です。

また、何らかの状態を追跡しながら入力文字を 1 文字ずつ処理する代わりに、単純な関数を入力に適用して実際の数値を取得します。これらの関数はすべて、標準ライブラリ関数の単なる合成です。

于 2012-04-07T01:37:26.780 に答える
5

ループには、nc、nw、nl、stateの4つの状態変数と、次の文字cがあります。ループは、ループを最後に通過したときのnc、nw、nl、および状態を記憶し、cはループを通過する各反復を変更します。代わりに、これらの変数をループから取り出して、ベクトル[state、nc、nw、nl]に配置するとします。次に、ループ構造を2つの引数を取る関数に変更します。1つ目はベクトル[state、nc、nw、nl]で、2つ目はcであり、更新されたnc、nw、nlの値を持つ新しいベクトルを返します。と状態。C風の擬似コード:

f([state, nc, nw, nl], c) {
    ++nc;
    if (c == '\n')
      ++nl;
    if (c == ' ' || c == '\n' || c = '\t')
      state = OUT;
    else if (state == OUT) {
      state = IN;
      ++nw;
    }
    return [state, nc, nw, nl];
}

これで、ベクトル[OUT、0、0、0]と文字列の最初の文字( "hello、world"など)を使用してその関数を呼び出すことができ、新しいベクトル[IN、1、0、0が返されます。 ]。この新しいベクトルと2番目の文字「e」を使用してfを再度呼び出すと、[IN、2、0、0]が返されます。文字列内の残りの文字について繰り返します。最後の呼び出しは、Cコードによって出力された値と同じ[IN、12、2、0]を返します。基本的な考え方は、状態変数をループから取り出し、ループの内臓を関数に変換し、状態変数のベクトルと次の入力をその関数の引数として渡し、新しい状態ベクトルを次のように返すことです。結果。これを行うreduceと呼ばれる関数があります。

Clojureでそれを行う方法は次のとおりです(返されるベクトルを強調するようにフォーマットされています):

(defn f [[state nc nw nl] c]
  (let [nl (if (= c \n)(inc nl) nl)]
    (cond
     (or (= c \space)(= c \n)(= c \t)) [:out  (inc nc) nw       nl]
     (= state :out)                    [:in   (inc nc) (inc nw) nl]
     true                              [state (inc nc) nw       nl]
)))

(defn wc [s] (reduce f [:out 0 0 0] s))

(wc "hello, world")

これは戻ります(そしてreplに出力します)[:in 12 2 0]

于 2012-04-07T04:42:48.987 に答える
5

これが、Schemeの純粋関数型、厳密、シングルパス、末尾再帰ソリューションでの私のショットです。

(define (word-count input-port)
  (let loop ((c (read-char input-port))
             (nl 0)
             (nw 0)
             (nc 0)
             (state 'out))
    (cond ((eof-object? c)
           (printf "nl: ~s, nw: ~s, nc: ~s\n" nl nw nc))
          ((char=? c #\newline)
           (loop (read-char input-port) (add1 nl) nw (add1 nc) 'out))
          ((char-whitespace? c)
           (loop (read-char input-port) nl nw (add1 nc) 'out))
          ((eq? state 'out)
           (loop (read-char input-port) nl (add1 nw) (add1 nc) 'in))
          (else
           (loop (read-char input-port) nl nw (add1 nc) state)))))

word-countinput portパラメータとしてを受け取ります。代わりに、追加のデータ構造(構造体、タプル、ベクトルなど)は作成されず、すべての状態がパラメーターに保持されることに注意してください。例として、これを含むファイル内の単語を数えるために:

hello, world

次のような手順を呼び出します。

(call-with-input-file "/path/to/file" word-count)
> nl: 0, nw: 2, nc: 12
于 2012-04-08T05:23:03.677 に答える
4

これは、私のブログからのプログラムの Scheme バージョンで、引数とファイルの処理を含む Unix ワード カウント プログラム全体を実装しています。重要な機能は、純粋に機能的な wc です。これは、すべてのローカル変数をローカル関数 (named-let で定義) の引数に移動します。これは、命令型ループを関数型スタイルに変換するための標準的なイディオムです。man ページとコードを以下に示します。

NAME

    wc -- word count

SYNOPSIS

    wc [ -lwc ] [ name ... ]

DESCRIPTION

    Wc counts lines, words and characters in the named files,
    or in the standard input if no name appears. A word is a
    maximal string of characters delimited by spaces, tabs or
    newlines.

    If the optional argument is present, just the specified
    counts (lines, words, or characters) are selected by the
    letters l, w or c.

#! /usr/bin/scheme --script

(define l-flag #t)
(define w-flag #t)
(define c-flag #t)

(define (update-flags fs)
  (if (not (member #\l fs)) (set! l-flag #f))
  (if (not (member #\w fs)) (set! w-flag #f))
  (if (not (member #\c fs)) (set! c-flag #f)))

(define (put-dec n width)
  (let* ((n-str (number->string n)))
    (display (make-string (- width (string-length n-str)) #\space))
    (display n-str)))

(define (wc)
  (let loop ((inword #f) (c (read-char)) (ls 0) (ws 0) (cs 0))
    (cond ((eof-object? c) (values ls ws cs))
          ((char=? c #\newline)
            (loop #f (read-char) (add1 ls) ws (add1 cs)))
          ((not (member c '(#\space #\newline #\tab)))
            (if inword
                (loop #t (read-char) ls ws (add1 cs))
                (loop #t (read-char) ls (add1 ws) (add1 cs))))
          (else (loop #f (read-char) ls ws (add1 cs))))))

(define (main args)
  (when (and (pair? args) (char=? (string-ref (car args) 0) #\-))
        (update-flags (cdr (string->list (car args))))
        (set! args (cdr args)))
  (if (null? args)
      (let-values (((ls ws cs) (wc)))
        (when l-flag (display ls) (display " "))
        (when w-flag (display ws) (display " "))
        (when c-flag (display cs) (display " "))
        (newline))
      (let loop ((args args) (l-tot 0) (w-tot 0) (c-tot 0))
        (if (null? args)
            (begin (when l-flag (put-dec l-tot 12))
                   (when w-flag (put-dec w-tot 12))
                   (when c-flag (put-dec c-tot 12)))
            (with-input-from-file (car args)
              (lambda ()
                (let-values (((ls ws cs) (wc)))
                  (when l-flag (put-dec ls 12))
                  (when w-flag (put-dec ws 12))
                  (when c-flag (put-dec cs 12))
                  (display " ") (display (car args)) (newline)
                  (loop (cdr args) (+ l-tot ls) (+ w-tot ws) (+ c-tot cs)))))))))     

(main (cdr (command-line)))
于 2012-04-08T14:35:25.593 に答える
2

Haskellでは怠惰ではなく厳密なIOを使用しています。単語のみを実行しますが、この上に文字や行を簡単に実装できます。textおよびconduitパッケージが必要です。

module Main
where

import Control.Applicative
import Data.Conduit
import qualified Data.Conduit.Binary as CB
import qualified Data.Conduit.List as CL
import qualified Data.Conduit.Text as CT
import qualified Data.Text as T
import System.Environment

main :: IO ()
main = do args <- getArgs
          print <$> (runResourceT $
            CB.sourceFile (args !! 0)
                $$  CB.lines
                =$= CT.decode CT.utf8
                =$= CL.map T.words
                =$  CL.fold (\acc words -> acc + length words) 0)
于 2012-04-08T15:17:51.797 に答える
2

これは、ここに投稿されているClojureの例に基づいていますが、再帰を使用したCLのソリューションです。

(defstruct (state (:constructor make-state (state chars words lines)))
  state chars words lines)


(defun wc (state stream)
  (symbol-macrolet ((s (state-state state))
                    (c (state-chars state))
                    (w (state-words state))
                    (l (state-lines state)))

    (case (read-char stream nil :eof)
      (:eof state)

      (#\Newline (wc (make-state :out (1+ c) w (1+ l)) stream))
      (#\Space   (wc (make-state :out (1+ c) w     l)  stream))

      (t (if (eq s :out)
             (wc (make-state :in (1+ c) (1+ w) l) stream)
             (wc (make-state :in (1+ c)     w  l) stream))))))


(with-input-from-string (stream "Hello Functional Programming World")
  (wc (make-state :out 0 0 0) stream))

;;; => #S(STATE:STATE:IN:CHARS 34:WORDS 4:LINES 0)

于 2012-04-07T13:15:53.263 に答える
2

入力を 1 回繰り返すだけでこれをいくらかエレガントに記述できると思いますが、GHC にもっと多くの作業を行わせる必要があります-O2

私はまだこのコードをコンパイルしていません。速度と Thomas DuBuisson の回答を比較することはあまりありませんが、これは基本的な方向性を示しているはずです。

{-# LANGUAGE BangPatterns #-}
import Data.List

wordcount = snd . foldl' go (False,0) 
  where  go (!b,!n) !c =  if  elem c [' ','\t','\n']  then  (False,n)
              else  (True, n + if b then 0 else 1)

linecount = foldl' go 0
  where  go !n !c = n + if c == '\n' then 1 else 0

main = interact $ show . go
  where  go x = (linecount x, wordcount x, foldl' (\!n _ ->n+1) 0 x)

ストリーム フュージョンを正しく理解していれば、GHC はインラインwordcountlinecountして に変換し、3 つのコマンドを 1 つmainにマージしfoldl'、うまくいけば if チェックの再配置を開始する必要があります。elemもちろん、それがインライン化されていることを願っていfoldl'ます。

そうでない場合は、確かにインライン化を強制し、おそらく単純な融合ルールを作成できますが、おそらくデフォルトで十分です. または、いくつかの単純な変更で目的の効果が得られる場合もあります。

ところで、私はfoldl' (\n _ ->n+1) 0 xについて悪い話を聞いたという理由だけで書きましたが、うまく動作するlengthかもしれません。プロファイリングする価値のある別の変更です。length

于 2012-04-07T23:07:20.660 に答える
1

match以下は、forループ マクロを使用した Typed Racket のバージョンです。

(: word-count : Input-Port -> Void)
(define (word-count in)
  (define-values (nl nw nc st)
    (for/fold: ([nl : Integer 0] [nw : Integer 0] [nc : Integer 0] 
                [state : (U 'in 'out) 'out])
      ([c (in-input-port-chars in)])
      (match* (c state)
        [(#\newline _) (values (add1 nl) nw (add1 nc) 'out)]
        [((? char-whitespace?) _)
         (values (add1 nl) nw (add1 nc) 'out)]
        [(_ 'out) (values nl (add1 nw) (add1 nc) 'in)]
        [(_ _) (values nl nw (add1 nc) state)])))
  (printf "nl: ~s, nw: ~s, nc: ~s\n" nl nw nc))
于 2012-04-10T19:43:12.327 に答える
1

これはHaskellの実装で、元のCプログラムが従うアプローチに近づけようとしました。反復はしばしば折り畳み操作になり、状態を含む変数が に渡される操作の最初の引数として終了しfoldます。

-- Count characters, words, and lines in an input string.
wordCount::String->(Int, Int, Int)
wordCount str = (c,w,l)
  where (inWord,c,w,l) = foldl op (False,0,0,1) str
          where op (inWord,c,w,l) next | next == '\n' = (False,c+1,w,l+1)
                                       | next == '\t' || next == ' ' = (False,c+1,w,l)
                                       | inWord == False = (True,c+1,w+1,l)
                                       | otherwise = (True,c+1,w,l)

main = interact $ show . wordCount
于 2012-04-16T19:21:20.497 に答える