Frage

I am using an existential type as a wrapper. At a point in my code where I know the enclosed type, I want to do something with it that is specific to the enclosed type. This is the closest I can get:

 {-# 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

The error I get is:

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.

How can I accomplish this? Thank you in advance for any suggestions.

War es hilfreich?

Lösung

Use 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 ()

Alternatively, consider declaring doSomethingWith in the Agent class, perhaps with a default definition.

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 ()

Finally, I should point out that your AgentBox type is an example of the existential typeclass anti-pattern, so you should perhaps ignore what I've written above and redesign your Agent class as an ordinary datatype.

Andere Tipps

Could not deduce (a ~ Bug).

We can, but the compiler can't.
We know that agentId is meant to be injective, so that two instances of different types have the same agentId String, but the compiler can't deduce that. Applying a function Agent a -> String loses whatever type information you had about a, and you didn't have much because it was existentially qualified.

Problem 1: Existential data types stop the compiler from using the type of the data. This is the heart of your problems. You decided you wanted them to be different types and then you decided you wanted them to be all one type.

Problem 2: Strings aren't types, types are. Better than Strings are user-defined types, eg

data Species = Bug | Saurapod | ....

but better than data is an actual type, don't make it then hide it.

Solution 1:

Avoid existential types. Instead of having a type class Agent, have a record type data Agent, making all Agents uniform.

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
    }

Solution 2:

Avoid existential types. Instead of having a type class providing an interface for agents, have a data type consisting of the necessary bits:

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

class IsAgent a where
  agent :: a -> Agent

Now you can have

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

Solution 3:

Avoid existential types. Instead of having existential Agents, have a union type of Agents

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 ++ ....

Solution 4:

Avoid existential types. Instead of having existential Agents, separate out generic Agent code, and have a union type of Agents including this

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 ....),
          ...]

Solution 5

Refuse to give up on existential types, choose to leave the joyous ease of static typing and use Dynamic or Typable or something else unfun to recover some type information.

You have to convince the type checker as well that you have the type is Bug. You can do this by making Data.Typeable.Typeable a super-class of Agent and then use Data.Typeable.cast to downcast from the existential type to the actual type.

But before doing this, consider doing it some other way. This is not very Haskellish, but rather in OO style.

{-# 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"
Lizenziert unter: CC-BY-SA mit Zuschreibung
Nicht verbunden mit StackOverflow
scroll top