Safe Haskell | None |
---|---|
Language | Haskell2010 |
Symantic.SharingObserver
Synopsis
- class Referenceable letName repr where
- class Definable letName repr where
- define :: letName -> repr a -> repr a
- class MakeLetName letName where
- makeLetName :: SharingName -> IO letName
- data SharingName = forall a. SharingName (StableName a)
- makeSharingName :: a -> SharingName
- newtype SharingObserver letName repr a = SharingObserver {
- unSharingObserver :: ReaderT (HashSet SharingName) (State (SharingObserverState letName)) (SharingFinalizer letName repr a)
- observeSharing :: Eq letName => Hashable letName => Show letName => SharingObserver letName repr a -> WithSharing letName repr a
- type WithSharing letName repr a = (repr a, HashMap letName (SomeLet repr))
- data SharingObserverState letName = SharingObserverState {
- oss_refs :: HashMap SharingName (letName, Int)
- oss_recs :: HashSet SharingName
- observeSharingNode :: Eq letName => Hashable letName => Show letName => Referenceable letName repr => MakeLetName letName => SharingObserver letName repr a -> SharingObserver letName repr a
- newtype SharingFinalizer letName repr a = SharingFinalizer {
- unFinalizeSharing :: ReaderT (HashSet letName) (Writer (LetBindings letName repr)) (repr a)
- class Letsable letName repr where
- lets :: LetBindings letName repr -> repr a -> repr a
- data SomeLet repr = forall a. SomeLet (repr a)
- type LetBindings letName repr = HashMap letName (SomeLet repr)
- type OpenRecs letName a = LetRecs letName (OpenRec letName a)
- type OpenRec letName a = LetRecs letName a -> a
- type LetRecs letName = HashMap letName
- fix :: (a -> a) -> a
- mutualFix :: forall recs a. Functor recs => recs (recs a -> a) -> recs a
Class Referenceable
class Referenceable letName repr where Source #
This class is not for end-users like usual symantic operators, though it will have to be defined on end-users' interpreters.
Minimal complete definition
Nothing
Methods
ref :: Bool -> letName -> repr a Source #
(
is a reference to ref
isRec letName)(letName)
.
It is introduced by observeSharing
.
(isRec)
is True
iif. this ref
erence is recursive,
ie. appears within its define
.
TODO: index letName
with a
to enable dependent-map
default ref :: FromDerived (Referenceable letName) repr => Bool -> letName -> repr a Source #
Instances
(Referenceable letName repr, Eq letName, Hashable letName, Show letName) => Referenceable letName (SharingFinalizer letName repr) Source # | |
Defined in Symantic.SharingObserver Methods ref :: Bool -> letName -> SharingFinalizer letName repr a Source # | |
Referenceable letName (SharingObserver letName repr) Source # | |
Defined in Symantic.SharingObserver Methods ref :: Bool -> letName -> SharingObserver letName repr a Source # |
Class Definable
class Definable letName repr where Source #
This class is not for end-users like usual symantic operators.
There should be not need to use it outside this module,
because used define
s are gathered in Letsable
.
Minimal complete definition
Nothing
Methods
define :: letName -> repr a -> repr a Source #
(
let-binds define
letName sub)(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.
default define :: FromDerived1 (Definable letName) repr => letName -> repr a -> repr a Source #
Instances
(Referenceable letName repr, Eq letName, Hashable letName, Show letName) => Definable letName (SharingFinalizer letName repr) Source # | |
Defined in Symantic.SharingObserver Methods define :: letName -> SharingFinalizer letName repr a -> SharingFinalizer letName repr a Source # | |
Definable letName (SharingObserver letName repr) Source # | |
Defined in Symantic.SharingObserver Methods define :: letName -> SharingObserver letName repr a -> SharingObserver letName repr a Source # |
Class MakeLetName
class MakeLetName letName where Source #
Methods
makeLetName :: SharingName -> IO letName Source #
Type SharingName
data SharingName Source #
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.
Constructors
forall a. SharingName (StableName a) |
Instances
Eq SharingName Source # | |
Defined in Symantic.SharingObserver | |
Hashable SharingName Source # | |
Defined in Symantic.SharingObserver |
makeSharingName :: a -> SharingName Source #
(
is like makeSharingName
x)(
but it also forces
evaluation of makeStableName
x)(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.
Type SharingObserver
newtype SharingObserver letName repr a Source #
Constructors
SharingObserver | |
Fields
|
Instances
observeSharing :: Eq letName => Hashable letName => Show letName => SharingObserver letName repr a -> WithSharing letName repr a Source #
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
Beware not to apply observeSharing
more than once on the same term
otherwise some define
introduced by the first call
would be removed by the second call.
Type WithSharing
type WithSharing letName repr a = (repr a, HashMap letName (SomeLet repr)) Source #
Type SharingObserverState
data SharingObserverState letName Source #
Constructors
SharingObserverState | |
Fields
|
observeSharingNode :: Eq letName => Hashable letName => Show letName => Referenceable letName repr => MakeLetName letName => SharingObserver letName repr a -> SharingObserver letName repr a Source #
Type SharingFinalizer
newtype SharingFinalizer letName repr a Source #
Constructors
SharingFinalizer | |
Fields
|
Instances
Class Letsable
class Letsable letName repr where Source #
Minimal complete definition
Nothing
Methods
lets :: LetBindings letName repr -> repr a -> repr a Source #
(
let-binds lets
defs x)(defs)
in (x)
.
default lets :: Derivable repr => FromDerived1 (Letsable letName) repr => LetBindings letName repr -> repr a -> repr a Source #
Instances
Letsable letName (SharingObserver letName repr) Source # | |
Defined in Symantic.SharingObserver Methods lets :: LetBindings letName (SharingObserver letName repr) -> SharingObserver letName repr a -> SharingObserver letName repr a Source # |
Type SomeLet
Type LetBindings
type LetBindings letName repr = HashMap letName (SomeLet repr) Source #
Type OpenRecs
type OpenRecs letName a = LetRecs letName (OpenRec letName a) Source #
Mutually recursive terms, in open recursion style.
type OpenRec letName a = LetRecs letName a -> a Source #
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).
mutualFix :: forall recs a. Functor recs => recs (recs a -> a) -> recs a Source #
Lest fixpoint combinator of mutually recursive terms.
(
takes a container of terms
in the open recursion style mutualFix
opens)(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