LOS*_*LOS 27 haskell pattern-matching bytestring pattern-synonyms
我是一个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)
Run Code Online (Sandbox Code Playgroud)
正如所料,这会过滤掉字符串中出现的所有"ab".但是,我在尝试将其应用于a时遇到问题ByteString.
天真的版本
dropR :: BS.ByteString -> BS.ByteString
dropR [] = []
dropR (x:[]) = [x]
<...>
Run Code Online (Sandbox Code Playgroud)
产量
Couldn't match expected type `BS.ByteString'
against inferred type `[a]'
In the pattern: []
In the definition of `dropR': dropR [] = []
Run Code Online (Sandbox Code Playgroud)
[]显然是罪魁祸首,因为它是一个常规String而非一个ByteString.Subbing in BS.empty似乎是正确的,但给出了"绑定位置的合格名称:BS.empty".离开我们去尝试
dropR :: BS.ByteString -> BS.ByteString
dropR empty = empty
dropR (x cons empty) = x cons empty
<...>
Run Code Online (Sandbox Code Playgroud)
这给出了"模式中的解析错误" (x cons empty).我真的不知道我还能在这做什么.
作为旁注,我正在尝试使用此函数来从某些文本中过滤掉特定的UTF16字符.如果有一个干净的方法来实现这一点,我很乐意听到它,但这种模式匹配错误似乎是新手哈克勒应该真正理解的东西.
Ed'*_*'ka 25
您可以使用视图模式进行此类操作
{-# 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)
Run Code Online (Sandbox Code Playgroud)
Ice*_*ack 11
最新版本的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))
Run Code Online (Sandbox Code Playgroud)
更进一步,您可以将其抽象为适用于任何类型类(如果我们获得关联的模式同义词,这将看起来更好).模式定义保持不变:
{-# 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 = (:)
Run Code Online (Sandbox Code Playgroud)
在这种情况下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))
Run Code Online (Sandbox Code Playgroud)
对于它的地狱:
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))
Run Code Online (Sandbox Code Playgroud)
你可以在我关于模式同义词的帖子上看到更多.
gaw*_*awi 10
模式使用数据构造函数.http://book.realworldhaskell.org/read/defining-types-streamlining-functions.html
你empty只是对第一个参数的绑定,它可能已经存在x并且它不会改变任何东西.
您无法在模式中引用正常函数,因此(x cons empty)不合法.注意:我猜(cons x empty)你的意思是真的,但这也是非法的.
ByteString与...截然不同String. String是别名[Char],所以它是一个真实的列表,:操作符可以用于模式.
ByteString是Data.ByteString.Internal.PS !(GHC.ForeignPtr.ForeignPtr GHC.Word.Word8) !Int !Int(即指向本机char*+ offset + length的指针).由于隐藏了ByteString的数据构造函数,因此必须使用函数来访问数据,而不是模式.
这里使用text包的UTF-16过滤器问题的解决方案(肯定不是最好的):
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)
Run Code Online (Sandbox Code Playgroud)
为此,我会在结果上进行模式匹配uncons :: ByteString -> Maybe (Word8, ByteString).
Haskell中的模式匹配仅适用于使用'data'或'newtype'声明的构造函数.ByteString类型不会导出您无法模式匹配的构造函数.