我正在尝试编写一个从文件中读取原始字节的函数,将其“转换”为“普通”类型,然后对其进行排序。
为了做到这一点,我需要告诉它应该如何解释二进制数据 - 即二进制数据的类型是什么。
为了使它成为“二进制”数据,在“我可以将此数据视为原始位,当我从磁盘读取和写入时”时,数据的类型必须是二进制和位。 而且,要对它进行排序,它必须是Ord的成员。
任何限制这些方式的类型都应该是可排序的。
作为一个小黑客,为了将类型传递给sort函数,我正在传递一个类型的居民。 (如果有办法传递类型并获得结果,我很想知道。)
{-# LANGUAGE RankNTypes #-}
import Data.Binary.Get
import Data.Binary.Put
type Sortable = forall a. (Bits a, Binary a, Ord a) => a
data SortOpts = SortOpts { maxFiles :: Int
, maxMemory :: Integer
, maxThreads :: Int
, binType :: Sortable
}
defaultOpts = SortOpts { maxFiles = 128
, maxMemory = 1000 * 1000 * 1000 * 1000
, maxThreads = 4
, binType = 0 :: Word32
};
putBinaryValues :: Binary a => Handle -> [a] -> IO ()
putBinaryValues out vals = do
let bytes = runPut . mapM_ put $ vals
BL.hPut out bytes
binaryValues :: (Binary a, Bits a) => a -> Handle -> IO [a]
binaryValues t inf = do
size <- hFileSize inf
let cast = runGet (genericReplicateM (size `div` byteWidth) get)
cast . BL.fromChunks . (:[]) <$> BS.hGetContents inf
where genericReplicateM n = sequence . (DL.genericReplicate n)
byteWidth = fromIntegral $ (bitSize t) `div` 8
但是这不能编译。显然Haskell坚持认为记录的所有值都是具体类型。至少,这是我从错误信息中收集的内容:
Could not deduce (a ~ Word32)
from the context (Bits a, Ord a, Binary a)
bound by a type expected by the context:
(Bits a, Ord a, Binary a) => a
at ...
`a' is a rigid type variable bound by
a type expected by the context: (Bits a, Ord a, Binary a) => a
那么,如何实现这种概括呢?
编辑:
我想使用记录更新语法来“配置”排序。 E.G:
configure = defaultOpts -- and exporting that
以后
let myOpts = configure{ binType = 42 :: Word16 }
但这不起作用,我不明白为什么,除非它只是纽约。
Record update for insufficiently polymorphic field: binType :: a
In the expression: configure {binType = words !! 0}
In an equation for `o': o = configure {binType = words !! 0}
In the expression:
do { inTestHandle <- inTest;
words <- testRandomWords;
putBinaryValues inTestHandle $ take 100 words;
seekBeg inTestHandle;
.... }
那么,我的客户端代码是否只需要从defaultOpts中逐步复制值并在每次想要重新配置排序时创建一条新记录?
答案 0 :(得分:8)
问题是RankNTypes
。查看Sortable
,这是一个将返回任意a
的函数,其中a
是Ord
,Bits
和{{1}的实例}。换句话说,那里没有3个类的实例,那里有所有实例。
Bytes
显然不能这样做,所以试图把它放在那里是一个错误。
将此视为Word32
,undefined
不是“某种类型与undefined
兼容”,它可以是所有类型。这相当于说
a
如果你想要一些词汇:foo :: a
foo = 1
是普遍量化的,那么调用者选择实现。你想要的是存在量化,被调用者选择具体类型。
所以最简单的补救措施是
a
并在每个函数上约束data SortOpts a = SortOpts {
maxFiles :: Int
, maxMemory :: Integer
, maxThreads :: Int
, binType :: a
}
a
为了简化输入,
someFun :: (Bits a, Bytes a, Ord a) => SortOpts a -> whatever
否则你需要创建一个存在主义的“拳击”类型。在这里,我使用GADT来做到这一点。
class (Ord a, Bytes a, Bits a) => Sortable a where
instance (Ord a, Bytes a, Bits a) => Sortable a where
然后在其上创建 {-# LANGUAGE GADTs #-}
data SortBox where
Sort :: (Bits a, Bytes a, Ord a) => a -> SortBox
,Bits
和Bytes
的实例,只需将隐藏的Ord
取消装箱并对其进行操作即可。这样,您就可以使用a
打包任何类型,然后将其统一用作Sort
,Bits
或Bytes
。它在类型级别是透明的,但在值级别,你必须填充奇怪的东西。
Ord
答案 1 :(得分:1)
您可以在SortOpts
类型中使用ExistentialQuantification
。以下编译:
{-# LANGUAGE ExistentialQuantification #-}
import Data.Bits
import Data.Word
import Data.Binary
import Data.Binary.Get
import Data.Binary.Put
data SortOpts = forall a. (Bits a, Binary a, Ord a) => SortOpts
{ maxFiles :: Int
, maxMemory :: Integer
, maxThreads :: Int
, binType :: a
}
defaultOpts = SortOpts
{ maxFiles = 128
, maxMemory = 1000 * 1000 * 1000 * 1000
, maxThreads = 4
, binType = 0 :: Word32
}
但是,请注意,您不能将binType
用作函数,因为它的类型为exists a. SortOpts -> a
,并且您不能将存在类型作为返回值。但是,您可以通过模式匹配来获取字段值,例如
test :: SortOpts -> ByteString -> ByteString -> Ordering
test (SortOpts{binType=binType}) bsa bsb = compare a b where
a = runGet get bsa `asTypeOf` binType
b = runGet get bsb `asTypeOf` binType
使用给定binType
中的存在SortOpts
对两个字节串进行反序列化和比较。
正如您所注意到的,Haskell的记录更新语法不支持存在字段,因此您需要执行以下操作来更新binType
:
defaultOpts = SortOpts
{ maxFiles = 128
, maxMemory = 1000 * 1000 * 1000 * 1000
, maxThreads = 4
, binType = 0 :: Word32
}
alternativeOpts = withBinType (0 :: Word16) $ defaultOpts
{ maxFiles = 256 }
withBinType :: (Bits a, Binary a, Ord a) => a -> SortOpts -> SortOpts
withBinType bt (SortOpts{..}) = SortOpts maxFiles maxMemory maxThreads bt
以上使用RecordWildCards
使记录复制更容易一些。在以后使用选项记录时,这也是一个方便的扩展。
或者,正如jozefg建议的那样,您可以使用binType
的包装类型。你可以这样使用它:
{-# LANGUAGE ExistentialQuantification #-}
data BinType = forall a. (Bits a, Binary a, Ord a) => BinType a
data SortOpts = SortOpts
{ maxFiles :: Int
, maxMemory :: Integer
, maxThreads :: Int
, binType :: BinType
}
defaultOpts = SortOpts
{ maxFiles = 128
, maxMemory = 1000 * 1000 * 1000 * 1000
, maxThreads = 4
, binType = BinType (0 :: Word32)
}
alternativeOpts = defaultOpts
{ binType = BinType (0 :: Word16) }
由于SortOpts
现在只是常规记录类型,因此您可以正常使用所有记录操作。要引用展开的binType
,您需要在包装器上进行模式匹配,以便之前的test
示例变为(使用RecordWildCards
)
test :: SortOpts -> ByteString -> ByteString -> Ordering
test (SortOpts{..}) bsa bsb = case binType of
BinType bt -> compare a b where
a = runGet get bsa `asTypeOf` bt
b = runGet get bsb `asTypeOf` bt
请注意,以上所有假设您都有一个特定的用例,您需要能够出于某种原因隐藏存在主义背后的确切类型参数。通常,您只需将类型参数保留在SortOpts
中,并将其约束在使用SortOpts
的函数中。即。
data SortOpts a = SortOpts
{ maxFiles :: Int
, maxMemory :: Integer
, maxThreads :: Int
, binType :: a
}
test :: (Bits a, Binary a, Ord a) => SortOpts a -> ByteString -> ByteString -> Ordering
test (SortOpts{..}) bsa bsb = compare a b where
a = runGet get bsa `asTypeOf` binType
b = runGet get bsb `asTypeOf` binType
如果需要,您可以使用ConstraintKinds
扩展名制作更短的别名,如
{-# LANGUAGE ConstraintKinds #-}
type BinType a = (Bits a, Binary a, Ord a)
test :: BinType a => SortOpts a -> ByteString -> ByteString -> Ordering