Interesting. You want to control a data type used *inside* an algorithm from outside. Here's a smaller version:
foo :: String -> String foo s = show (read s) This is ambiguous; what type should 'read' return? Your idea: pass in that type via a proxy value: foo :: (Read a, Show a) => a -> String -> String foo p s = show (read s `asTypeOf` p) Now you can say foo (undefined :: Int) "34" and it'll work. A neater way to do this with GHC is to use scoped type variables: foo :: (Read a, Show a) => a -> String -> String foo (p::a) s = show (read s :: a) One reason this is neater is that it scales up better when you want to pass a type constructor instead of a type. First define a data type with no constructors, and a phantom type arg data Proxy (a :: * -> *) Now you can write a function like this f :: (MArray a ix e) => Proxy a -> .... f (p :: Proxy a) ... = do { (arr :: a ix e) <- newArray ... The type variable 'a' is bound by the (Proxy a) pattern, and scopes over the body. The type variables 'ix' and 'e' in the do-binding are bound right there (since they aren't already in scope). Another use for phantom types! Simon | -----Original Message----- | From: Hal Daume III [mailto:hdaume@;ISI.EDU] | Sent: 03 November 2002 19:31 | To: Haskell Mailing List | Subject: getting the right types | | Hi all, | | I have a function which essentially looks like this: | | f my_data = do | a1 <- newArray ... | ... | a2 <- newArray ... | g my_data a1 a2 | | where f is a monadic operation essentially of type 'a -> m a'. The | problem is that when this function isn't given a type signature, you get | something like: | | f :: (MArray a1 p e, MArray a2 p e) => t | | where a1 and a2 aren't bound in t. Now, I could provide a type signature | on the array expressions, something like: | | ... (a1 :: IOArray Int Int) <- newArray ... | | but i would like to be able to use unboxed arrays when possible, and i | don't want to bind the funtion to be in IO. My current solution is to | define: | | data ArrayType arr prob = forall ix . ArrayType (arr ix prob) | asArray :: arr ix prob -> ArrayType arr prob -> arr ix prob | a `asArray` _ = a | | Sort of like asTypeOf. Then, I change f to: | | f :: (MArray arr p e) => ArrayType arr p -> t -> m t | f arr_type ... = ... | | And inside f I have a function: | | newArray_arr bnds init = | do a <- newArray bnds init | return (a `asArray` arr_type) | | This enables me to create arrays of arbitrary representation with the same | values but different indices (which is important). | | However, this strikes me as horribly hackish. Is there some better way to | do this? | | - Hal | | -- | Hal Daume III | | "Computer science is no more about computers | [EMAIL PROTECTED] | than astronomy is about telescopes." -Dijkstra | www.isi.edu/~hdaume | | _______________________________________________ | Haskell mailing list | [EMAIL PROTECTED] | http://www.haskell.org/mailman/listinfo/haskell _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell