'Caching' of results of default instance definitions
Viktor Dukhovni
ietf-dane at dukhovni.org
Wed Nov 23 03:46:17 UTC 2022
On Wed, Nov 23, 2022 at 12:28:46PM +1100, Clinton Mead wrote:
> I have a class with a "method" which has a default definition, and that
> default definition has no arguments on the LHS, will a separate "instance"
> of that default definition be created for each instance of that class that
> inherits that default definition? The important consequence of that being
> that the default definition is only computed once per type.
Typically, an instance method will have the instance type variable
present in either one of the parameter types or in the result type,
making it possible to infer at call sites which instance to invoke.
Such methods are polymorphic, and rarely admit a sensible default value.
However, when a such a default value is possible, and if you disable
any inlining that might trigger separate per call site evaluation,
then indeed you can get a "once per-type" value. The below prints
"Foo wuz here" only three times.
Main.hs:
module Main (main) where
import Again
import M
main :: IO ()
main = do
print $ one : foo
print $ 'X' : foo
print $ [one] : foo
again
where one = 1 :: Int
Again.hs:
module Again(again) where
import M
{-# NOINLINE again #-}
again :: IO ()
again = do
print $ one : foo
print $ 'X' : foo
print $ [one] : foo
where one = 1 :: Int
M.hs
{-# LANGUAGE FlexibleInstances #-}
module M (foo) where
import Debug.Trace
class M a where
{-# NOINLINE foo #-}
foo :: [a]
foo = trace "Foo wuz here" $ []
instance M Int
instance M Char
instance M ([Int])
With `TypeApplications` and `AllowAmbiguousTypes`, you can define
non-polymorphic instance methods that require an explicit type
application at the call site. In that case, with inlining disabled and
optimisation enabled, the various default `foo @sometype` calls can be
collapsed to a single constant across multiple types.
M.hs:
{-# LANGUAGE AllowAmbiguousTypes, FlexibleInstances #-}
{-# OPTIONS_GHC -O2 #-}
module M (foo) where
import Debug.Trace
class M a where
{-# NOINLINE foo #-}
foo :: Int
foo = trace "Foo wuz here" $ 42
instance M Int
instance M Char
instance M ([Int])
With the above class definition and instance definitions and the print
statements necessarily written with type applications:
print $ foo @Int
print $ foo @Char
print $ foo @[Int]
the trace string is printed just once.
--
Viktor.
More information about the ghc-devs
mailing list