28

我是 Haskell 新手,在弄清楚如何模式匹配ByteString. 我的[Char]函数版本如下所示:

dropAB :: String -> String
dropAB []       = []
dropAB (x:[])   = x:[]
dropAB (x:y:xs) = if x=='a' && y=='b'
                  then dropAB xs
                  else x:(dropAB $ y:xs) 

正如预期的那样,这会从字符串中过滤掉所有出现的“ab”。但是,我在尝试将其应用于ByteString.

天真的版本

dropR :: BS.ByteString -> BS.ByteString
dropR []         = []
dropR (x:[])     = [x]
<...>

产量

Couldn't match expected type `BS.ByteString'
       against inferred type `[a]'
In the pattern: []
In the definition of `dropR': dropR [] = []

[]显然是罪魁祸首,因为它是常规String而不是ByteString. 插入BS.empty似乎是正确的,但在绑定位置给出了“限定名称:BS.empty”。让我们尝试

dropR :: BS.ByteString -> BS.ByteString
dropR empty              = empty        
dropR (x cons empty)     = x cons empty
<...>

这给出了“模式中的解析错误” (x cons empty)。我真的不知道我还能在这里做什么。

作为旁注,我试图用这个函数做的是从一些文本中过滤掉一个特定的 UTF16 字符。如果有一种干净的方法可以实现这一点,我很想听听,但是这种模式匹配错误似乎是新手haskeller 应该真正理解的。

4

5 回答 5

26

您可以将视图模式用于此类事情

{-# LANGUAGE ViewPatterns #-}    
import Data.ByteString (ByteString, cons, uncons, singleton, empty)
import Data.ByteString.Internal (c2w) 

dropR :: ByteString -> ByteString
dropR (uncons -> Nothing) = empty
dropR (uncons -> Just (x,uncons -> Nothing)) = singleton x
dropR (uncons -> Just (x,uncons -> Just(y,xs))) =
    if x == c2w 'a' && y == c2w 'b'
    then dropR xs
    else cons x (dropR $ cons y xs)
于 2010-10-30T10:14:59.573 回答
13

最新版本的 GHC (7.8) 有一个称为模式同义词的功能,可以添加到 gawi 的示例中:

{-# LANGUAGE ViewPatterns, PatternSynonyms #-}

import Data.ByteString (ByteString, cons, uncons, singleton, empty)
import Data.ByteString.Internal (c2w)

infixr 5 :<

pattern b :< bs <- (uncons -> Just (b, bs))
pattern Empty   <- (uncons -> Nothing)

dropR :: ByteString -> ByteString
dropR Empty          = empty
dropR (x :< Empty)   = singleton x
dropR (x :< y :< xs)
  | x == c2w 'a' && y == c2w 'b' = dropR xs
  | otherwise                    = cons x (dropR (cons y xs))

更进一步,您可以将其抽象为适用于任何类型类(当/如果我们获得关联的模式同义词时,这看起来会更好)。模式定义保持不变:

{-# LANGUAGE ViewPatterns, PatternSynonyms, TypeFamilies #-}

import qualified Data.ByteString as BS
import Data.ByteString (ByteString, singleton)
import Data.ByteString.Internal (c2w)
import Data.Word

class ListLike l where
  type Elem l

  empty  :: l
  uncons :: l -> Maybe (Elem l, l)
  cons   :: Elem l -> l -> l

instance ListLike ByteString where
  type Elem ByteString = Word8

  empty  = BS.empty
  uncons = BS.uncons
  cons   = BS.cons

instance ListLike [a] where
  type Elem [a] = a

  empty         = []
  uncons []     = Nothing
  uncons (x:xs) = Just (x, xs)
  cons          = (:)

在这种情况下,dropR可以同时处理[Word8]ByteString

-- dropR :: [Word8]    -> [Word8]
-- dropR :: ByteString -> ByteString
dropR :: (ListLike l, Elem l ~ Word8) => l -> l
dropR Empty          = empty
dropR (x :< Empty)   = cons x empty
dropR (x :< y :< xs)
  | x == c2w 'a' && y == c2w 'b' = dropR xs
  | otherwise                    = cons x (dropR (cons y xs))

而对于它的地狱:

import Data.ByteString.Internal (w2c)

infixr 5 :•    
pattern b :• bs <- (w2c -> b) :< bs

dropR :: (ListLike l, Elem l ~ Word8) => l -> l
dropR Empty              = empty
dropR (x   :< Empty)     = cons x empty
dropR ('a' :• 'b' :• xs) = dropR xs
dropR (x   :< y   :< xs) = cons x (dropR (cons y xs))

您可以在我关于模式同义词的帖子中看到更多信息。

于 2014-05-23T16:07:38.417 回答
10

模式使用数据构造函数。http://book.realworldhaskell.org/read/defining-types-streamlining-functions.html

empty只是第一个参数的绑定,它可能是x并且它不会改变任何东西。

你不能在你的模式中引用一个正常的函数,所以(x cons empty)是不合法的。注意:我想(cons x empty)这确实是您的意思,但这也是非法的。

ByteString与 完全不同StringString是 的别名[Char],所以它是一个真实的列表,并且该:运算符可以在模式中使用。

ByteString 是Data.ByteString.Internal.PS !(GHC.ForeignPtr.ForeignPtr GHC.Word.Word8) !Int !Int(即指向本机 char* + 偏移量 + 长度的指针)。由于 ByteString 的数据构造函数是隐藏的,因此您必须使用函数来访问数据,而不是模式。


这是使用包解决 UTF-16 过滤器问题的解决方案(当然不是最好的解决方案)text

module Test where

import Data.ByteString as BS
import Data.Text as T
import Data.Text.IO as TIO
import Data.Text.Encoding

removeAll :: Char -> Text -> Text
removeAll c t =  T.filter (/= c) t

main = do
  bytes <- BS.readFile "test.txt"
  TIO.putStr $ removeAll 'c' (decodeUtf16LE bytes)
于 2010-10-30T00:49:32.993 回答
6

为此,我将对uncons :: ByteString -> Maybe (Word8, ByteString).

Haskell 中的模式匹配仅适用于使用 'data' 或 'newtype' 声明的构造函数。ByteString 类型不会导出您无法进行模式匹配的构造函数。

于 2010-10-30T01:05:36.457 回答
2

只是为了解决您收到的错误消息及其含义:

Couldn't match expected type `BS.ByteString'
       against inferred type `[a]'
In the pattern: []
In the definition of `dropR': dropR [] = []

所以编译器期望你的函数是类型的:BS.ByteString -> BS.ByteString因为你在你的签名中给了它那个类型。然而,它推断(通过查看函数的主体)该函数实际上是 type [a] -> [a]。那里存在不匹配,因此编译器会抱怨。

问题是您将 (:) 和 [] 视为语法糖,而它们实际上只是列表类型的构造函数(与 ByteString 非常不同)。

于 2010-10-30T17:54:28.230 回答