Re: [GHC Users] Dictionary sharing

2012-07-02 Thread Bertram Felgenhauer
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

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


[GHC Users] Dictionary sharing

2012-06-29 Thread Jonas Almström Duregård
Hi,

Is there a way to ensure that functions in a class instance are
treated as top level definitions and not re-evaluated?

For instance if I have this:

class C a where
  list :: [a]

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

How can I ensure that list :: [[X]] is evaluated at most once for any
type X (throughout my program)?

I assume this is potentially harmful, since list can never be garbage
collected and there may exist an unbounded number of X's.

I currently have a solution that uses Typeable to memoise the result
of the function based on its type. Is there an easier way?

Regards,
Jonas

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC Users] Dictionary sharing

2012-06-29 Thread Edward Z. Yang
Hello Jonas,

Like other top-level definitions, these instances are considered CAFs
(constant applicative forms), so these instances will in fact usually
be evaluated only once per type X.

import System.IO.Unsafe
class C a where
dflt :: a
instance C Int where
dflt = unsafePerformIO (putStrLn bang  return 2)
main = do
print (dflt :: Int)
print (dflt :: Int)
print (dflt :: Int)

ezyang@javelin:~/Dev/haskell$ ./caf
bang
2
2
2

Cheers,
Edward

Excerpts from Jonas Almström Duregård's message of Fri Jun 29 07:25:42 -0400 
2012:
 Hi,
 
 Is there a way to ensure that functions in a class instance are
 treated as top level definitions and not re-evaluated?
 
 For instance if I have this:
 
 class C a where
   list :: [a]
 
 instance List a = List [a] where
   list = permutations list
 
 How can I ensure that list :: [[X]] is evaluated at most once for any
 type X (throughout my program)?
 
 I assume this is potentially harmful, since list can never be garbage
 collected and there may exist an unbounded number of X's.
 
 I currently have a solution that uses Typeable to memoise the result
 of the function based on its type. Is there an easier way?
 
 Regards,
 Jonas
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC Users] Dictionary sharing

2012-06-29 Thread Jonas Almström Duregård
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.

The real issue I was having was actually not with a list but with a
memoised function i.e. something like:

class C a where
  memoised :: Int - a


Perhaps functions are treated differently?

Regards,
Jonas

On 29 June 2012 15:55, Edward Z. Yang ezy...@mit.edu wrote:
 Hello Jonas,

 Like other top-level definitions, these instances are considered CAFs
 (constant applicative forms), so these instances will in fact usually
 be evaluated only once per type X.

    import System.IO.Unsafe
    class C a where
        dflt :: a
    instance C Int where
        dflt = unsafePerformIO (putStrLn bang  return 2)
    main = do
        print (dflt :: Int)
        print (dflt :: Int)
        print (dflt :: Int)

 ezyang@javelin:~/Dev/haskell$ ./caf
 bang
 2
 2
 2

 Cheers,
 Edward

 Excerpts from Jonas Almström Duregård's message of Fri Jun 29 07:25:42 -0400 
 2012:
 Hi,

 Is there a way to ensure that functions in a class instance are
 treated as top level definitions and not re-evaluated?

 For instance if I have this:
 
 class C a where
   list :: [a]

 instance List a = List [a] where
   list = permutations list
 
 How can I ensure that list :: [[X]] is evaluated at most once for any
 type X (throughout my program)?

 I assume this is potentially harmful, since list can never be garbage
 collected and there may exist an unbounded number of X's.

 I currently have a solution that uses Typeable to memoise the result
 of the function based on its type. Is there an easier way?

 Regards,
 Jonas


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [GHC Users] Dictionary sharing

2012-06-29 Thread Edward Z. Yang
I say usually because while I believe this to be true for the
current implementation of GHC, I don't think we necessary give
this operational guarantee.

But yes, your real problem is that there is a world of difference between
functions and non-functions.  You will need to use one of the usual tricks for
memoising functions, or forgo using a function altogether and lean on laziness.

Edward

Excerpts from Jonas Almström Duregård's message of Fri Jun 29 11:21:46 -0400 
2012:
 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.
 
 The real issue I was having was actually not with a list but with a
 memoised function i.e. something like:
 
 class C a where
   memoised :: Int - a
 
 
 Perhaps functions are treated differently?
 
 Regards,
 Jonas
 
 On 29 June 2012 15:55, Edward Z. Yang ezy...@mit.edu wrote:
  Hello Jonas,
 
  Like other top-level definitions, these instances are considered CAFs
  (constant applicative forms), so these instances will in fact usually
  be evaluated only once per type X.
 
     import System.IO.Unsafe
     class C a where
         dflt :: a
     instance C Int where
         dflt = unsafePerformIO (putStrLn bang  return 2)
     main = do
         print (dflt :: Int)
         print (dflt :: Int)
         print (dflt :: Int)
 
  ezyang@javelin:~/Dev/haskell$ ./caf
  bang
  2
  2
  2
 
  Cheers,
  Edward
 
  Excerpts from Jonas Almström Duregård's message of Fri Jun 29 07:25:42 
  -0400 2012:
  Hi,
 
  Is there a way to ensure that functions in a class instance are
  treated as top level definitions and not re-evaluated?
 
  For instance if I have this:
  
  class C a where
    list :: [a]
 
  instance List a = List [a] where
    list = permutations list
  
  How can I ensure that list :: [[X]] is evaluated at most once for any
  type X (throughout my program)?
 
  I assume this is potentially harmful, since list can never be garbage
  collected and there may exist an unbounded number of X's.
 
  I currently have a solution that uses Typeable to memoise the result
  of the function based on its type. Is there an easier way?
 
  Regards,
  Jonas
 

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users