haskell-jp / beginners #14 at 2021-02-03 11:36:08 +0900

入力処理で、1回の入力単位が1行であれば、hGetLine hdl でよいのですが、
1回の入力単位が複数の改行を含み特定の文字列(たとえば"\n>>> ")が出現するまで、
という場合どう書けばいいでしょうか。
こういうことですか

import           

hGetLineUntil :: Handle -> String -> IO String
hGetLineUntil hdl marker = go ""
 where
  go accum = do
    line <- hGetLine hdl
    if line == marker
      then return accum
      else go $ accum ++ line ++ "\n"


main :: IO ()
main =
  print =<< hGetLineUntil stdin ">>>"
ああ、説明不足でした、特定の文字列というのは或る種のプロンプトであることを想定していまして、
プロンプトの後は一文字も来ていない時点で取得したいのです。
プロンプトは来ていても、改行文字は来ないので、hGetLineではプロンプトが得られない状況です。
とりあえず、書いてみたのですが、入出力が不得意すぎて、なんだかなコードのような気がしています。
hGetUntil :: Handle -> String -> IO String
hGetUntil h str = do
    { eof <- hIsEOF h
    ; if eof then return ""
      else do
          { c <- hGetChar h
          ; if c == head str then (c :) <$> getStr (tail str)
            else (c :) <$> hGetUntil h str
          }
    }
    where
        getStr []     = return ""
        getStr (c:cs) = do
            { eof <- hIsEOF h
            ; if eof then return ""
              else do
                  { c' <- hGetChar h
                  ; if c == c' then (c' :) <$> getStr cs
                    else (c' :) <$> hGetUntil h str
                  }
            }

やりたいことはこういうことだったりしますか?
{-# LANGUAGE OverloadedStrings #-}

module Main where

import qualified              as S
import qualified Data.ByteString.Char8 as BS
import           Data.IORef            (IORef, newIORef, readIORef, writeIORef)
import           System.IO.Unsafe      (unsafePerformIO)

mkBuffer :: IO (IORef BS.ByteString)
mkBuffer = newIORef ""

hGetUntil :: S.Handle -> IORef BS.ByteString -> BS.ByteString -> IO BS.ByteString
hGetUntil h ref marker = do
  prevRemain <- readIORef ref
  (item, remain) <- go prevRemain
  writeIORef ref remain
  return item
 where
  go prevRemain =
    if BS.null bs2
      then do
        mBs <- getBs prevRemain
        case mBs of
          Nothing     -> return (prevRemain, "")
          Just remain -> go remain
      else return (bs1, bs3)
   where
    (bs1, bs2) = BS.breakSubstring marker prevRemain
    bs3        = BS.drop (BS.length marker) bs2
  getBs :: BS.ByteString -> IO (Maybe BS.ByteString)
  getBs prev = do
    isEOF <- S.hIsEOF h
    if isEOF
      then return Nothing
      else do
        True <- S.hWaitForInput h (-1)
        Just . BS.append prev <$> BS.hGetNonBlocking h 1024

main :: IO ()
main = do
  buf <- mkBuffer
  print =<< hGetUntil S.stdin buf "\n>>>"

(IORefは必須ではないですが、どこかに情報をためて受け渡したりする必要があります)
REPLのラッパーを書こうとしいます。*ユーザーの入力(改行終端)ごと*にREPLからの出力(プロンプト文字列終端)を表示するものです。
模式的には、以下の(1)〜(3)の要素を繋げてループにする(あるいはそれぞれをループにしてから繋げる)イメージです。

(1)  (stdin & hgetLine        ) >>= (INPUT-FILTER  >>> hPutStrLn oh1   )
(2)  (ih1   & hGetLine        ) >>= (REPL          >>> hPutStr   oh2   )
(3)  (ih2   & hGetUntil prompt) >>= (OUTPUT-FILTER >>> hPutStr   stdout)