使用conkin
软件包:https://hackage.haskell.org/package/conkin
我希望能够取出任何Conkin.Traversable
并将其转储到Tuple
中,并留下 indices 到该Tuple
中,以便我可以对其进行重构
我正在使用一些语言扩展名:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
模块声明
module TupleDump where
进口
import Control.Monad.State (State, runState)
import qualified Control.Monad.State as State
import Data.Functor.Compose (getCompose)
import Data.Functor.Const (Const (Const), getConst)
import Conkin (Dispose (..), Flip (..), Tuple (..))
import qualified Conkin
我不想不必使用unsafeCoerce,但看不到解决方法:
import Unsafe.Coerce (unsafeCoerce)
我们将Index
定义为:
data Index (xs :: [k]) (x :: k) where
IZ :: Index (x ': xs) x
IS :: Index xs i -> Index (x ': xs) i
我们可以使用索引从Tuple
中提取项目:
(!) :: Tuple xs a -> Index xs x -> a x
(!) (Cons x _) IZ = x
(!) (Cons _ xs) (IS i) = xs ! i
我们应该能够将Conkin.Traversable
实例的所有内容提取并转储到Tuple
到data TupleDump t a = forall xs. TupleDump (t (Index xs)) (Tuple xs a)
toTupleDump :: forall (t :: (k -> *) -> *) (a :: k -> *). Conkin.Traversable t
=> t a -> TupleDump t a
fromTupleDump :: Conkin.Functor t => TupleDump t a -> t a
的位置,并在每个元素的后面保留索引。然后从索引的结构和元组可以重构原始的Traversable结构:
fromTupleDump (TupleDump inds vals) = Conkin.fmap (vals !) inds
重建部分很简单:
toTupleDump
这个问题专门用于实现unsafeCoerce
。以下是我到目前为止的最佳尝试:
它涉及许多辅助功能和一个data Some (a :: k -> *) = forall (x :: k). Some (a x)
现有量化的函子:
Int
给出一个Index
,构造一些mkIndex :: Tuple xs a -> Int -> Some (Index xs)
mkIndex Nil _ = error "Index out of bounds"
mkIndex _ n | n < 0 = error "Index out of bounds"
mkIndex (Cons _ _) 0 = Some IZ
mkIndex (Cons _ xs) n = case mkIndex xs (n - 1) of Some i -> Some $ IS i
:
Tuple
给出一系列存在量化的函子,将它们分组为(翻转的)fromList :: [Some a] -> Some (Flip Tuple a)
fromList [] = Some $ Flip Nil
fromList (Some x : xs) = case fromList xs of
Some (Flip t) -> Some (Flip (Cons x t))
:
Prelude.Applicative
在Conkin.Applicative
(而不是traverseInPrelude :: (Prelude.Applicative f, Conkin.Traversable t)
=> (forall x. a x -> f (b x)) -> t a -> f (t b)
traverseInPrelude fn t =
Conkin.fmap (unComposeConst . getFlip) . getCompose <$>
getDispose (Conkin.traverse (Dispose . fmap ComposeConst . fn) t)
newtype ComposeConst a b c = ComposeConst {unComposeConst :: a b}
)内进行遍历
toTupleDump
现在我们可以定义toTupleDump t =
:
Int
我们首先将索引跟踪为(:)
,然后将元素转储到普通列表中。
由于我们使用 let
nextItem :: forall (x :: k). a x -> State (Int, [Some a]) (Const Int x)
nextItem x = do
(i, xs') <- State.get
State.put (i + 1, Some x : xs')
return $ Const i
(res, (_, xs)) = runState (traverseInPrelude nextItem t) (0, [])
in
构建列表,因此它将倒退。
Tuple
现在,我们反转列表并将其转换为 case fromList (reverse xs) of
Some (Flip (tup :: Tuple xs a)) ->
:
fmap
我们需要在res
结构上Int
将所有Index
更改为 let
indexedRes = Conkin.fmap (coerceIndex . mkIndex tup . getConst) res
es
unsafeCoerce
这里是 coerceIndex :: forall x. Some (Index xs) -> Index xs x
coerceIndex (Some i) = unsafeCoerce i
in
TupleDump indexedRes tup
。由于此方法涉及两次遍历结构,因此我们必须让类型检查器知道第二遍,其类型参数与第一遍相同。
Hashtable ht = new Hashtable();
ht.put(Context.INITIAL_CONTEXT_FACTORY,
"weblogic.jndi.WLInitialContextFactory");
ht.put(Context.PROVIDER_URL, "t3://acmeCluster:7001");
try {
Context ctx = new InitialContext(ht);
// Do the client's work
}
catch (NamingException ne) {
// A failure occurred
}
finally {
try {ctx.close();}
catch (Exception e) {
// a failure occurred
}
}
答案 0 :(得分:2)
我猜想如果没有toTupleDump
,就不可能实现unsafeCoerce
。
可以将问题简化为计算fillWithIndexes
data SomeIndex t = forall xs. SomeIndex (t (Index xs))
fillWithIndexes :: forall (t :: (k -> *) -> *) (a :: k -> *). Conkin.Traversable t
=> t a -> SomeIndex t
其中xs
是遍历类型t a
的值所收集的类型的列表。但是,类型系统不能保证对结果t (Index xs)
的遍历会产生相同的类型xs
列表。
如果Traversable
的{{1}}实例不遵守t
法则,则可以设计一个实际上改变类型的实现。
Traversable
我们不能通过假设data T a = TBool (a Bool) | TChar (a Char)
instance Conkin.Functor T where
fmap f (TBool a) = TBool (f a)
fmap f (TChar a) = TChar (f a)
instance Conkin.Foldable T where
foldr f z (TBool a) = f a z
foldr f z (TChar a) = f a z
instance Conkin.Traversable T where
traverse f (TBool a) = Conkin.pure (Compose (TChar undefined))
traverse f (TChar a) = Conkin.pure (Compose (TBool undefined))
法则排除这种情况吗?是的,我们可以排除它,但是类型检查器不能,这意味着我们必须使用Traversable
。