
{-# LANGUAGE EmptyDataDecls #-} module Main (main) where import Unsafe.Coerce data Anything newtype Key x = Key Int deriving Eq type Dict = [(Key Anything, Anything)] put :: Key x -> x -> Dict -> Dict put k' v' = raw (unsafeCoerce k') (unsafeCoerce v') where raw k0 v0 [] = [(k0,v0)] raw k0 v0 ((k,v):zs) | k == k0 = (k0 ,v0) : zs | otherwise = (k ,v ) : raw k0 v0 zs get :: Key x -> Dict -> Maybe x get k' zs = unsafeCoerce (raw (unsafeCoerce k') zs) where raw k0 [] = Nothing raw k0 ((k,v):zs) | k == k0 = Just v | otherwise = raw k0 zs main = do let k1 = Key 1 :: Key Int let k2 = Key 2 :: Key Double let k3 = Key 3 :: Key String let k4 = Key 4 :: Key Bool let d0 = [] let d1 = put k1 123 d0 let d2 = put k2 123 d1 let d3 = put k3 "123" d2 let d4 = put k4 True d3 print (get k1 d4) print (get k2 d4) print (get k3 d4) print (get k4 d4) Unsafe coerce, anyone? This particular example appears to run without incident, but the GHC docs suggest that this is very... well, unsafe. (In particular, the docs claim this will fall over on function types.) I presume there's some less-evil way of doing this?

It looks like you may want
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Dynamic.html
. It does more or less what you're talking about behind the scenes,
but probably uses the magical Any type to not encounter issues with
functions, and gives you a Nothing if you attempt to coerce it to the
wrong type.
On Thu, Oct 15, 2009 at 5:10 PM, Andrew Coppin
{-# LANGUAGE EmptyDataDecls #-}
module Main (main) where
import Unsafe.Coerce
data Anything
newtype Key x = Key Int deriving Eq
type Dict = [(Key Anything, Anything)]
put :: Key x -> x -> Dict -> Dict put k' v' = raw (unsafeCoerce k') (unsafeCoerce v') where raw k0 v0 [] = [(k0,v0)] raw k0 v0 ((k,v):zs) | k == k0 = (k0 ,v0) : zs | otherwise = (k ,v ) : raw k0 v0 zs
get :: Key x -> Dict -> Maybe x get k' zs = unsafeCoerce (raw (unsafeCoerce k') zs) where raw k0 [] = Nothing raw k0 ((k,v):zs) | k == k0 = Just v | otherwise = raw k0 zs
main = do let k1 = Key 1 :: Key Int let k2 = Key 2 :: Key Double let k3 = Key 3 :: Key String let k4 = Key 4 :: Key Bool
let d0 = [] let d1 = put k1 123 d0 let d2 = put k2 123 d1 let d3 = put k3 "123" d2 let d4 = put k4 True d3
print (get k1 d4) print (get k2 d4) print (get k3 d4) print (get k4 d4)
Unsafe coerce, anyone?
This particular example appears to run without incident, but the GHC docs suggest that this is very... well, unsafe. (In particular, the docs claim this will fall over on function types.)
I presume there's some less-evil way of doing this?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Maybe you would like the hetero-map package. Its purpose is to do
precisely what you are doing, but in a typesafe way.
On Thu, Oct 15, 2009 at 3:10 PM, Andrew Coppin
{-# LANGUAGE EmptyDataDecls #-}
module Main (main) where
import Unsafe.Coerce
data Anything
newtype Key x = Key Int deriving Eq
type Dict = [(Key Anything, Anything)]
put :: Key x -> x -> Dict -> Dict put k' v' = raw (unsafeCoerce k') (unsafeCoerce v') where raw k0 v0 [] = [(k0,v0)] raw k0 v0 ((k,v):zs) | k == k0 = (k0 ,v0) : zs | otherwise = (k ,v ) : raw k0 v0 zs
get :: Key x -> Dict -> Maybe x get k' zs = unsafeCoerce (raw (unsafeCoerce k') zs) where raw k0 [] = Nothing raw k0 ((k,v):zs) | k == k0 = Just v | otherwise = raw k0 zs
main = do let k1 = Key 1 :: Key Int let k2 = Key 2 :: Key Double let k3 = Key 3 :: Key String let k4 = Key 4 :: Key Bool
let d0 = [] let d1 = put k1 123 d0 let d2 = put k2 123 d1 let d3 = put k3 "123" d2 let d4 = put k4 True d3
print (get k1 d4) print (get k2 d4) print (get k3 d4) print (get k4 d4)
Unsafe coerce, anyone?
This particular example appears to run without incident, but the GHC docs suggest that this is very... well, unsafe. (In particular, the docs claim this will fall over on function types.)
I presume there's some less-evil way of doing this?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (3)
-
Andrew Coppin
-
Daniel Peebles
-
Luke Palmer