{-# LANGUAGE AllowAmbiguousTypes #-} -- For ShowLetName {-# LANGUAGE BangPatterns #-} -- For makeSharingName {-# LANGUAGE DataKinds #-} -- For ShowLetName {-# LANGUAGE ExistentialQuantification #-} -- For SharingName -- {-# LANGUAGE MagicHash #-} -- For unsafeCoerce# module Symantic.ObserveSharing where import Control.Applicative (Applicative(..)) import Control.Monad (Monad(..)) import Data.Bool import Data.Eq (Eq(..)) import Data.Function (($), (.)) import Data.Functor (Functor, (<$>)) import Data.Functor.Compose (Compose(..)) import Data.HashMap.Strict (HashMap) import Data.HashSet (HashSet) import Data.Hashable (Hashable, hashWithSalt, hash) import Data.Int (Int) import Data.Maybe (Maybe(..), isNothing) import Data.Monoid (Monoid(..)) import Data.Ord (Ord(..)) import Data.String (String) -- import GHC.Exts (Int(..)) -- import GHC.Prim (unsafeCoerce#) import GHC.StableName (StableName(..), makeStableName, hashStableName, eqStableName) -- import Numeric (showHex) import Prelude ((+), error) import System.IO (IO) import System.IO.Unsafe (unsafePerformIO) import Text.Show (Show(..)) import qualified Control.Monad.Trans.Class as MT import qualified Control.Monad.Trans.Reader as MT import qualified Control.Monad.Trans.State as MT import qualified Control.Monad.Trans.Writer as MT import qualified Data.HashMap.Strict as HM import qualified Data.HashSet as HS import Symantic.Derive -- * Class 'Referenceable' -- | This class is not for end-users like usual symantic operators, -- though it will have to be defined on end-users' interpreters. class Referenceable letName repr where -- | @('ref' isRec letName)@ is a reference to @(letName)@. -- It is introduced by 'observeSharing'. -- @(isRec)@ is 'True' iif. this 'ref'erence is recursive, -- ie. appears within its 'def'inition. -- -- TODO: index 'letName' with 'a' to enable dependent-map ref :: Bool -> letName -> repr a ref isRec name = liftDerived (ref isRec name) default ref :: FromDerived (Referenceable letName) repr => Bool -> letName -> repr a -- * Class 'Definable' -- | This class is not for end-users like usual symantic operators. -- There should be not need to use it outside this module, -- because used 'def'initions are gathered in 'Letsable'. class Definable letName repr where -- | @('def' letName sub)@ let-binds @(letName)@ to be equal to @(sub)@. -- This is a temporary node either replaced -- by 'ref' and an entry in 'lets''s 'LetBindings', -- or removed when no 'ref'erence is made to it. def :: letName -> repr a -> repr a def name = liftDerived1 (def name) default def :: FromDerived1 (Definable letName) repr => letName -> repr a -> repr a -- * Class 'MakeLetName' class MakeLetName letName where makeLetName :: SharingName -> IO letName -- ** Type 'ShowLetName' -- | Useful on golden unit tests because 'StableName's -- change often when changing unrelated source code -- or even when changing basic GHC or executable flags. class ShowLetName (showName::Bool) letName where showLetName :: letName -> String -- | Like 'Show'. instance Show letName => ShowLetName 'True letName where showLetName = show -- | Always return @""@, instance ShowLetName 'False letName where showLetName _p = "" -- * Type 'SharingName' -- | Note that the observable sharing enabled by 'StableName' -- is not perfect as it will not observe all the sharing explicitely done. -- -- Note also that the observed sharing could be different between ghc and ghci. data SharingName = forall a. SharingName (StableName a) -- | @('makeSharingName' x)@ is like @('makeStableName' x)@ but it also forces -- evaluation of @(x)@ to ensure that the 'StableName' is correct first time, -- which avoids to produce a tree bigger than needed. -- -- Note that this function uses 'unsafePerformIO' instead of returning in 'IO', -- this is apparently required to avoid infinite loops due to unstable 'StableName' -- in compiled code, and sometimes also in ghci. -- -- Note that maybe [pseq should be used here](https://gitlab.haskell.org/ghc/ghc/-/issues/2916). makeSharingName :: a -> SharingName makeSharingName !x = SharingName $ unsafePerformIO $ makeStableName x instance Eq SharingName where SharingName x == SharingName y = eqStableName x y instance Hashable SharingName where hash (SharingName n) = hashStableName n hashWithSalt salt (SharingName n) = hashWithSalt salt n {- instance Show SharingName where showsPrec _ (SharingName n) = showHex (I# (unsafeCoerce# n)) -} -- * Type 'ObserveSharing' newtype ObserveSharing letName repr a = ObserveSharing { unObserveSharing :: MT.ReaderT (HashSet SharingName) (MT.State (ObserveSharingState letName)) (FinalizeSharing letName repr a) } -- | Interpreter detecting some (Haskell embedded) @let@ definitions used at -- least once and/or recursively, in order to replace them -- with the 'lets' and 'ref' combinators. -- See [Type-safe observable sharing in Haskell](https://doi.org/10.1145/1596638.1596653) -- -- Beware not to apply 'observeSharing' more than once on the same term -- otherwise some 'def' introduced by the first call -- would be removed by the second call. observeSharing :: Eq letName => Hashable letName => Show letName => ObserveSharing letName repr a -> WithSharing letName repr a observeSharing (ObserveSharing m) = let (fs, st) = MT.runReaderT m mempty `MT.runState` ObserveSharingState { oss_refs = HM.empty , oss_recs = HS.empty } in let refs = HS.fromList [ letName | (letName, refCount) <- HM.elems (oss_refs st) , refCount > 0 ] in --trace (show refs) $ MT.runWriter $ (`MT.runReaderT` refs) $ unFinalizeSharing fs -- ** Type 'WithSharing' type WithSharing letName repr a = (repr a, HM.HashMap letName (SomeLet repr)) {- -- * Type 'WithSharing' data WithSharing letName repr a = WithSharing { lets :: HM.HashMap letName (SomeLet repr) , body :: repr a } mapWithSharing :: (forall v. repr v -> repr v) -> WithSharing letName repr a -> WithSharing letName repr a mapWithSharing f ws = WithSharing { lets = (\(SomeLet repr) -> SomeLet (f repr)) <$> lets ws , body = f (body ws) } -} -- ** Type 'ObserveSharingState' data ObserveSharingState letName = ObserveSharingState { oss_refs :: HashMap SharingName (letName, Int) , oss_recs :: HashSet SharingName } observeSharingNode :: Eq letName => Hashable letName => Show letName => Referenceable letName repr => MakeLetName letName => ObserveSharing letName repr a -> ObserveSharing letName repr a observeSharingNode (ObserveSharing m) = ObserveSharing $ do let nodeName = makeSharingName m st <- MT.lift MT.get ((letName, seenBefore), seen) <- getCompose $ HM.alterF (\seenBefore -> -- Compose is used to return (letName, seenBefore) along seen -- in the same HashMap lookup. Compose $ return $ case seenBefore of Nothing -> ((letName, seenBefore), Just (letName, 0)) where letName = unsafePerformIO $ makeLetName nodeName Just (letName, refCount) -> ((letName, seenBefore), Just (letName, refCount + 1)) ) nodeName (oss_refs st) parentNames <- MT.ask if nodeName `HS.member` parentNames then do -- recursive reference to nodeName: -- update seen references -- and mark nodeName as recursive MT.lift $ MT.put st { oss_refs = seen , oss_recs = HS.insert nodeName (oss_recs st) } return $ ref True letName else do -- non-recursive reference to nodeName -- update seen references -- and recurse if the nodeName hasn't been seen before -- (would be in a preceding sibling branch, not in parentNames). MT.lift $ MT.put st{ oss_refs = seen } if isNothing seenBefore then MT.local (HS.insert nodeName) (def letName <$> m) else return $ ref False letName type instance Derived (ObserveSharing letName repr) = FinalizeSharing letName repr instance ( Referenceable letName repr , MakeLetName letName , Eq letName , Hashable letName , Show letName ) => LiftDerived (ObserveSharing letName repr) where liftDerived = observeSharingNode . ObserveSharing . return instance ( Referenceable letName repr , MakeLetName letName , Eq letName , Hashable letName , Show letName ) => LiftDerived1 (ObserveSharing letName repr) where liftDerived1 f a = observeSharingNode $ ObserveSharing $ f <$> unObserveSharing a instance ( Referenceable letName repr , MakeLetName letName , Eq letName , Hashable letName , Show letName ) => LiftDerived2 (ObserveSharing letName repr) where liftDerived2 f a b = observeSharingNode $ ObserveSharing $ f <$> unObserveSharing a <*> unObserveSharing b instance ( Referenceable letName repr , MakeLetName letName , Eq letName , Hashable letName , Show letName ) => LiftDerived3 (ObserveSharing letName repr) where liftDerived3 f a b c = observeSharingNode $ ObserveSharing $ f <$> unObserveSharing a <*> unObserveSharing b <*> unObserveSharing c instance ( Referenceable letName repr , MakeLetName letName , Eq letName , Hashable letName , Show letName ) => LiftDerived4 (ObserveSharing letName repr) where liftDerived4 f a b c d = observeSharingNode $ ObserveSharing $ f <$> unObserveSharing a <*> unObserveSharing b <*> unObserveSharing c <*> unObserveSharing d instance Referenceable letName (ObserveSharing letName repr) where ref = error "[BUG]: observeSharing MUST NOT be applied twice" instance Definable letName (ObserveSharing letName repr) where def = error "[BUG]: observeSharing MUST NOT be applied twice" instance Letsable letName (ObserveSharing letName repr) where lets = error "[BUG]: observeSharing MUST NOT be applied twice" -- * Type 'FinalizeSharing' -- | Remove 'def' when non-recursive or unused -- or replace it by 'ref', moving 'def's to the top. newtype FinalizeSharing letName repr a = FinalizeSharing { unFinalizeSharing :: MT.ReaderT (HS.HashSet letName) (MT.Writer (LetBindings letName repr)) (repr a) } type instance Derived (FinalizeSharing _letName repr) = repr instance (Eq letName, Hashable letName) => LiftDerived (FinalizeSharing letName repr) where liftDerived = FinalizeSharing . pure instance (Eq letName, Hashable letName) => LiftDerived1 (FinalizeSharing letName repr) where liftDerived1 f a = FinalizeSharing $ f <$> unFinalizeSharing a instance (Eq letName, Hashable letName) => LiftDerived2 (FinalizeSharing letName repr) where liftDerived2 f a b = FinalizeSharing $ f <$> unFinalizeSharing a <*> unFinalizeSharing b instance (Eq letName, Hashable letName) => LiftDerived3 (FinalizeSharing letName repr) where liftDerived3 f a b c = FinalizeSharing $ f <$> unFinalizeSharing a <*> unFinalizeSharing b <*> unFinalizeSharing c instance (Eq letName, Hashable letName) => LiftDerived4 (FinalizeSharing letName repr) where liftDerived4 f a b c d = FinalizeSharing $ f <$> unFinalizeSharing a <*> unFinalizeSharing b <*> unFinalizeSharing c <*> unFinalizeSharing d instance ( Referenceable letName repr , Eq letName , Hashable letName , Show letName ) => Referenceable letName (FinalizeSharing letName repr) where ref isRec = liftDerived . ref isRec instance ( Referenceable letName repr , Eq letName , Hashable letName , Show letName ) => Definable letName (FinalizeSharing letName repr) where def name body = FinalizeSharing $ do refs <- MT.ask let (repr, defs) = MT.runWriter $ MT.runReaderT (unFinalizeSharing body) refs if name `HS.member` refs then do -- This 'def' is 'ref'erenced: move it into the result, -- to put it in scope even when some 'ref' to it exists outside of 'body' -- (which can happen when a body-expression is shared), -- and replace it by a 'ref'. MT.lift $ MT.tell $ HM.insert name (SomeLet repr) defs return $ ref False name else -- Remove this unreferenced 'def' node. unFinalizeSharing body -- ** Class 'Letsable' class Letsable letName repr where -- | @('lets' defs x)@ let-binds @(defs)@ in @(x)@. lets :: LetBindings letName repr -> repr a -> repr a lets defs = liftDerived1 (lets ((\(SomeLet val) -> SomeLet (derive val)) <$> defs)) default lets :: Derivable repr => FromDerived1 (Letsable letName) repr => LetBindings letName repr -> repr a -> repr a -- *** Type 'SomeLet' data SomeLet repr = forall a. SomeLet (repr a) -- *** Type 'LetBindings' type LetBindings letName repr = HM.HashMap letName (SomeLet repr) {- -- | Not used but can be written nonetheless. instance ( Letsable letName repr , Eq letName , Hashable letName , Show letName ) => Letsable letName (FinalizeSharing letName repr) where lets defs x = FinalizeSharing $ do ds <- traverse (\(SomeLet v) -> do r <- unFinalizeSharing v return (SomeLet r) ) defs MT.lift $ MT.tell ds unFinalizeSharing x -} -- *** Type 'OpenRecs' -- | Mutually recursive terms, in open recursion style. type OpenRecs letName a = LetRecs letName (OpenRec letName a) -- | Mutually recursive term, in open recursion style. -- The term is given a @final@ (aka. @self@) map -- of other terms it can refer to (including itself). type OpenRec letName a = LetRecs letName a -> a -- | Recursive let bindings. type LetRecs letName = HM.HashMap letName -- | Least fixpoint combinator. fix :: (a -> a) -> a fix f = final where final = f final -- | Lest fixpoint combinator of mutually recursive terms. -- @('mutualFix' opens)@ takes a container of terms -- in the open recursion style @(opens)@, -- and return that container of terms with their knots tied-up. -- -- Used to express mutual recursion and to transparently introduce memoization, -- between observed sharing ('defLet', 'call', 'jump') -- and also between join points ('defJoin', 'refJoin'). -- -- Here all mutually dependent functions are restricted to the same polymorphic type @(a)@. -- See http://okmij.org/ftp/Computation/fixed-point-combinators.html#Poly-variadic mutualFix :: forall recs a. Functor recs => recs ({-finals-}recs a -> a) -> recs a mutualFix opens = fix f where f :: recs a -> recs a f recs = ($ recs) <$> opens