[GHC Users] Dictionary sharing

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Mon Jul 2 20:11:53 CEST 2012


Jonas Almström Duregård wrote:
> Thank you for your response Edward,
> 
> You write that it is usually only evaluated once, do you know the
> circumstances under which it is evaluated more than once? I have some
> examples of this but they are all very large.

Only the dictionaries for type class instances that do not depend on
other instances will be CAFs and evaluated at most once. When an
instance has such dependencies, as for example (from your initial
mail in this thread),

    instance List a => List [a] where
        list = permutations list

then dictionaries will be created on demand (causing re-evaluation of
'list' in this particular case). More precisely, when the compiler
finds that a function needs a List [a] instance where only a List a
instance is available, it will create a fresh dictionary for List [a]
using the above implementation.

I am not aware of GHC providing any caching or memoisation mechanism
for this, so I think that your solution of building your own using
Typeable is appropriate.

Best regards,

Bertram

-- Example program showing addresses of various Ord dictionaries.
-- Contents may be hazardous if swallowed! Keep away from children!
{-# LANGUAGE MagicHash, Rank2Types #-}
module Main where

import GHC.Exts
import GHC.Int

newtype GetDict = GetDict { unGetDict :: forall a . Ord a => a -> Int }

-- Evil hack for extracting the address of a dictionary from a function
-- call. Note that these addresses may change during GC!
getDict :: Ord a => a -> Int
getDict = unGetDict (unsafeCoerce# getDict') where
    getDict' :: Addr# -> Addr# -> Int
    getDict' d _ = I# (addr2Int# d)

{-# NOINLINE bar #-}
-- newListDict is designed to force the creation of a new Ord [a]
-- dictionary given an Ord a dictionary, and return the new dictionary's
-- address.
getListDict :: Ord a => a -> Int
getListDict x = unGetDict (GetDict (\x -> getDict [x])) x

main = do
    print $ getDict (1 :: Int)      -- using a CAF dictionary
    print $ getDict (2 :: Int)      -- same as previous
    print $ getDict (2 :: Word)     -- a different CAF dictionary
    print $ getDict ([1] :: [Int])  -- also a CAF!
    print $ getDict ([2] :: [Int])  -- same as previous
    print $ getListDict (1 :: Int)  -- a dynamically created dictionary
    print $ getListDict (2 :: Int)  -- different from previous



More information about the Glasgow-haskell-users mailing list