记录中的多态类型

mas*_*onk 6 haskell

我正在尝试编写一个从文件中读取原始字节的函数,将其"转换"为"普通"类型,然后对其进行排序.

为了做到这一点,我需要告诉它应该如何解释二进制数据 - 即二进制数据的类型是什么.

为了使它成为"二进制"数据,在"我可以将此数据视为原始位,当我从磁盘读取和写入时"时,数据的类型必须是二进制和位.而且,要对它进行排序,它必须是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
Run Code Online (Sandbox Code Playgroud)

但这不编译.显然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
Run Code Online (Sandbox Code Playgroud)

那么,我怎么实现这种概括呢?

编辑:

我想使用记录更新语法来"配置"排序.例如:

configure = defaultOpts -- and exporting that
Run Code Online (Sandbox Code Playgroud)

然后

let myOpts = configure{ binType = 42 :: Word16 }
Run Code Online (Sandbox Code Playgroud)

但这不起作用,我不太明白为什么,除非它只是纽约.

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;
       .... }
Run Code Online (Sandbox Code Playgroud)

那么,我的客户端代码是否只需要从defaultOpts零碎地复制值并在每个想要重新配置排序时创建一条新记录?

Dan*_*zer 8

问题

问题是RankNTypes.看Sortable,这是它会返回一个任意的功能a,在这里a是一个实例Ord,BitsBytes.换句话说,那里没有3个类的实例,那里有所有实例.

Word32 显然不能这样做,所以试图把它放在那里是一个错误.

想想这个undefined,undefined不是"某种类型兼容a",它可以是所有类型.这相当于说

foo :: a
foo = 1
Run Code Online (Sandbox Code Playgroud)

如果你想要一些词汇:a是普遍量化的,那么调用者选择实现.你想要的是存在量化,被调用者选择具体类型.

可能的修复

所以最简单的补救措施是

data SortOpts a = SortOpts { 
    maxFiles :: Int
    , maxMemory :: Integer
    , maxThreads :: Int
    , binType    :: a
}
Run Code Online (Sandbox Code Playgroud)

并限制a每个功能

 someFun :: (Bits a, Bytes a, Ord a) => SortOpts a -> whatever
Run Code Online (Sandbox Code Playgroud)

为了方便打字,

 class (Ord a, Bytes a, Bits a) => Sortable a where
 instance (Ord a, Bytes a, Bits a) => Sortable a where
Run Code Online (Sandbox Code Playgroud)

否则你需要创建一个存在的"拳击"类型.在这里,我使用GADT来做到这一点.

 {-# LANGUAGE GADTs #-}

 data SortBox where
     Sort :: (Bits a, Bytes a, Ord a) => a -> SortBox
Run Code Online (Sandbox Code Playgroud)

然后创建的实例Bits,Bytes以及Ord通过简单地拆箱隐藏它a,操作它.这使你可以框起来任何类型的Sort,然后用它统称为一个Bits,BytesOrd.它在类型级别是透明的,但在值级别,你必须填充奇怪的东西.

data SortOpts a = SortOpts { 
    maxFiles :: Int
    , maxMemory :: Integer
    , maxThreads :: Int
    , binType    :: SortBox
}
Run Code Online (Sandbox Code Playgroud)


sha*_*ang 1

ExistentialQuantification您可以在您的类型中使用SortOpts。编译如下:

{-# 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
    }
Run Code Online (Sandbox Code Playgroud)

但是,请注意,您不能用作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
Run Code Online (Sandbox Code Playgroud)

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
Run Code Online (Sandbox Code Playgroud)

上述用途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) }
Run Code Online (Sandbox Code Playgroud)

由于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
Run Code Online (Sandbox Code Playgroud)

请注意,上述所有内容都假设您有一个特定的用例,您需要能够出于某种原因将确切的类型参数隐藏在存在性后面。通常,您只需保留类型参数SortOpts并将其限制在使用 的函数中SortOpts。IE

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
Run Code Online (Sandbox Code Playgroud)

如果需要,您可以使用ConstraintKinds扩展名创建更短的别名,如下所示

{-# LANGUAGE ConstraintKinds #-}

type BinType a = (Bits a, Binary a, Ord a)

test :: BinType a => SortOpts a -> ByteString -> ByteString -> Ordering
Run Code Online (Sandbox Code Playgroud)