2

我正在使用存在类型作为包装器。在我知道封闭类型的代码中,我想用它做一些特定于封闭类型的事情。这是我能得到的最接近的:

 {-# LANGUAGE ExistentialQuantification #-}

class Agent a where
  agentId :: a -> String
  speciesId :: a -> String
  -- plus other functions that all agents support

-- | A wrapper allowing my daemon to read and write agents of any species.
--   (Agents are stored in files that contain a tag so I know which function
--   to call to read the agent.)
data AgentBox = forall a. Agent a => AgentBox { unbox :: a }

instance Agent AgentBox where
  agentId (AgentBox a) = agentId a
  speciesId (AgentBox a) = speciesId a
  -- plus other functions that all agents support

bugTag :: String
bugTag = "Bug"

data Bug = Bug String

instance Agent Bug where
  agentId (Bug name) = name
  speciesId _ = bugTag

doSomethingWith :: AgentBox -> IO ()
doSomethingWith a = do
  if speciesId a == bugTag
    then do
      -- Now I know it's a bug, and I want to do something bug-specific
      doBugStuff2 a
      return ()
    else return ()

doBugStuff :: Bug -> IO ()
doBugStuff a = putStrLn $ agentId a ++ " does bug stuff"

doBugStuff2 AgentBox{unbox=a} = doBugStuff (a `asTypeOf` model) -- line 39
  where model = undefined :: Bug

我得到的错误是:

Amy30.hs:39:45:
    Could not deduce (a ~ Bug)
    from the context (Agent a)
      bound by a pattern with constructor
                 AgentBox :: forall a. Agent a => a -> AgentBox,
               in an equation for `doBugStuff2'
      at Amy30.hs:39:13-29
      `a' is a rigid type variable bound by
          a pattern with constructor
            AgentBox :: forall a. Agent a => a -> AgentBox,
          in an equation for `doBugStuff2'
          at Amy30.hs:39:13
    In the first argument of `asTypeOf', namely `a'
    In the first argument of `doBugStuff', namely
      `(a `asTypeOf` model)'
    In the expression: doBugStuff (a `asTypeOf` model)
Failed, modules loaded: none.

我怎样才能做到这一点?提前感谢您的任何建议。

4

3 回答 3

8

使用Data.Dynamic

import Data.Dynamic

class Typeable a => Agent a where
  agentId :: a -> String
  -- no need for speciesId

fromAgentBox :: Agent a => AgentBox -> Maybe a
fromAgentBox (AgentBox inner) = fromDynamic (toDyn inner)

instance Agent Bug where
  agentId (Bug name) = name
  -- no need for speciesId

doSomethingWith :: AgentBox -> IO ()
doSomethingWith a = do
  case fromAgentBox a of
    Just bug -> do
      -- Now the compiler knows it's a bug, and I can do something bug-specific
      doBugStuff2 bug
      return ()
    Nothing -> return ()

或者,考虑doSomethingWithAgent类中声明,可能使用默认定义。

class Agent a where
  agentId :: a -> String
  -- still don't need speciesId
  doSomethingWith :: a -> IO ()
  doSomethingWith _ = return ()

instance Agent Bug where
  agentId (Bug name) = name
  -- still don't need speciesId
  doSomethingWith bug = do
    -- Now the compiler knows it's a bug, and I can do something bug-specific
    doBugStuff2 bug
    return ()

最后,我应该指出,您的AgentBox类型是存在类型类反模式的一个示例,因此您或许应该忽略我上面写的内容,并将您的Agent类重新设计为普通数据类型。

于 2012-10-11T15:26:29.220 回答
4

Could not deduce (a ~ Bug).

我们可以,但编译器不能。
我们知道这agentId单射的,因此不同类型的两个实例具有相同的字符串,但编译器无法推断出这一点。应用一个函数会丢失你所拥有的任何类型信息,并且你没有太多,因为它是存在限定的。agentIdAgent a -> Stringa

问题 1:现有数据类型阻止编译器使用数据类型。这是你问题的核心。你决定你希望它们是不同的类型,然后你决定你希望它们都是一种类型。

问题 2:字符串不是类型,类型是。比字符串更好的是用户定义的类型,例如

data Species = Bug | Saurapod | ....

但比数据更好的是实际类型,不要让它然后隐藏它。

解决方案1:

避免存在类型。与其拥有类型类Agent,不如拥有一个记录类型data Agent,使所有代理统一。

data Agent = Agent {
    agentId :: String,
    speciesId :: Species,
    -- ...other stuff agents need. 
    -- Species-specific data is an illusion; 
    -- make Agent widely useful, catering for the eventualities
    }

解决方案2:

避免存在类型。与其让类型类为代理提供接口,不如让数据类型由必要的位组成:

data Agent = Agent {
    agentId :: String,
    speciesId :: Species,
    -- ...other stuff _all_ agents need. 
    }

class IsAgent a where
  agent :: a -> Agent

现在你可以拥有

agents::[Agent]
agents = map agent bugs 
      ++ map agent saurapods 
      ++ ...

解决方案3:

避免存在类型。有一个联合类型的代理,而不是存在的代理

class Agent a where
   -- all the stuff you want
instance Agent Bug where
   ...
instance Agent Saurapod where
   ...
data AnyAgent = ABug Bug | ASaurapod Saurapod | ... 
   -- ensure you have an agent instance for each type you need

instance Agent AnyAgent where
   -- much boilerplate code unwrapping and applying

agents :: [AnyAgent]
agents = map ABug bugs ++ map ASaurapod saurapods ++ ....

解决方案4:

避免存在类型。而不是存在代理,分离出通用代理代码,并有一个联合类型的代理,包括这个

data Agent = Agent {
    agentId :: String,
    -- ...other stuff _all_ agents need. 
    }

data Bug = Bug --..... Bug-specific data
data Saurapod = Saurapod --... Saurapod-specific data

data AnyAgent = ABug Agent Bug | ASaurapod Agent Saurapod | ... 

agent :: AnyAgent -> Agent
agent (ABug a _) = a
agent (ASaurapod a _) = a
...

agents :: [AnyAgent]
agents = [ABug (Agent {agentId="007", ...}) (Bug ....),
          ASaurapod (Agent {agentId="Pat", ...}) (Saurapod ....),
          ...]

解决方案 5

拒绝放弃存在的类型,选择离开静态类型和使用Dynamic或其他不有趣的Typable东西来恢复一些类型信息的乐趣。

于 2012-10-11T16:54:17.457 回答
3

您还必须让类型检查器相信您的类型是Bug. 您可以通过创建Data.Typeable.Typeable一个超类来做到这一点Agent,然后使用Data.Typeable.cast它从存在类型向下转换为实际类型。

但在这样做之前,请考虑以其他方式进行。这不是很 Haskellish,而是 OO 风格。

{-# LANGUAGE ExistentialQuantification, DeriveDataTypeable #-}
import Data.Typeable
import Data.Maybe

class Typeable a => Agent a where
  agentId :: a -> String
  speciesId :: a -> String

data AgentBox = forall a. Agent a => AgentBox { unbox :: a }
    deriving (Typeable)

instance Agent AgentBox where
  agentId (AgentBox a) = agentId a
  speciesId (AgentBox a) = speciesId a

bugTag :: String
bugTag = "Bug"

data Bug = Bug String
    deriving (Typeable)

instance Agent Bug where
  agentId (Bug name) = name
  speciesId _ = bugTag

doSomethingWith :: AgentBox -> IO ()
doSomethingWith a = do
  case cast a of
    Just bug -> doBugStuff bug
    Nothing -> return ()

doBugStuff :: Bug -> IO ()
doBugStuff a = putStrLn $ agentId a ++ " does bug stuff"
于 2012-10-11T15:29:29.713 回答