如何在haskell中建模所谓的“异构图”,以便可以在编译时验证图的类型正确性?

为此,异类图是一组节点,每个节点都有一个特定的类型标签,以及一组边,每个边缘都具有一个源类型的标签和一个目标类型的标签。

我们希望静态地确保在将边添加到图形时,该边的源类型标签与源节点的类型标签匹配,并且该边的目标类型标签与目标节点的类型标签匹配。但是我们不希望以琐碎的方式做到这一点(通过强制整个图只包含带有一个特定类型标签的节点)。

最佳答案

我不确定如何在编译时强制执行此操作(我认为这要求您的图完全是静态的吗?),但是在运行时使用Typeable强制执行相对比较简单。这是外观的草图。首先,我将从键入的NodeEdge类型开始:

data Node a = Node a
data Edge a b = Edge !Int !Int

将它们包装在存在中:
{-# LANGUAGE ExistentialQuantification #-}

import Data.Typeable

data SomeNode
  = forall a. (Typeable a)
  => SomeNode (Node a)

data SomeEdge
  = forall a b. (Typeable a, Typeable b)
  => SomeEdge (Edge a b)

具有使用现有量化类型的异构图数据类型:
import Data.IntMap (IntMap)

-- Not a great representation, but simple for illustration.
data Graph = Graph !(IntMap SomeNode) [SomeEdge]

然后执行动态类型检查的操作:
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

import qualified Data.IntMap as IntMap

addNode
  :: forall a. (Typeable a)
  => Int -> a -> Graph -> Maybe Graph
addNode i x (Graph ns es) = case IntMap.lookup i ns of

  -- If a node already exists at a given index:
  Just (SomeNode (existing :: Node e)) -> case eqT @e @a of

    -- Type-preserving replacement is allowed, but…
    Just Refl -> Just $ Graph ns' es

    -- …*type-changing* replacement is *not* allowed,
    -- since it could invalidate existing edges.
    Nothing -> Nothing

  -- Insertion is of course allowed.
  Nothing -> Just $ Graph ns' es

  where
    ns' = IntMap.insert i (SomeNode (Node x)) ns

-- To add an edge:
addEdge
  :: forall a b. (Typeable a, Typeable b)
  => Edge a b -> Graph -> Maybe Graph
addEdge e@(Edge f t) (Graph ns es) = do

  -- The ‘from’ node must exist…
  SomeNode (fn :: Node tfn) <- IntMap.lookup f ns
  -- …and have the correct type; and
  Refl <- eqT @a @tfn

  -- The ‘to’ node must exist…
  SomeNode (tn :: Node ttn) <- IntMap.lookup t ns
  -- …and have the correct type.
  Refl <- eqT @b @ttn

  pure $ Graph ns $ SomeEdge e : es

现在成功了:
pure (Graph mempty mempty)
  >>= addNode 0 (1 :: Int)
  >>= addNode 1 ('x' :: Char)
  >>= addEdge (Edge 0 1 :: Edge Int Char)

但是将Int中的Char/Edge Int Char更改为无效类型,或将0/1更改为无效索引,将失败并返回Nothing

10-06 10:30