Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Referenceable letName repr where
- class Definable letName repr where
- def :: letName -> repr a -> repr a
- class MakeLetName letName where
- makeLetName :: SharingName -> IO letName
- data SharingName = forall a. SharingName (StableName a)
- makeSharingName :: a -> SharingName
- newtype ObserveSharing letName repr a = ObserveSharing {
- unObserveSharing :: ReaderT (HashSet SharingName) (State (ObserveSharingState letName)) (FinalizeSharing letName repr a)
- observeSharing :: Eq letName => Hashable letName => Show letName => ObserveSharing letName repr a -> WithSharing letName repr a
- type WithSharing letName repr a = (repr a, HashMap letName (SomeLet repr))
- 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
- newtype FinalizeSharing letName repr a = FinalizeSharing {
- 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.
Nothing
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 def
inition.
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 (FinalizeSharing letName repr) Source # | |
Defined in Symantic.ObserveSharing ref :: Bool -> letName -> FinalizeSharing letName repr a Source # | |
Referenceable letName (ObserveSharing letName repr) Source # | |
Defined in Symantic.ObserveSharing ref :: Bool -> letName -> ObserveSharing 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 def
initions are gathered in Letsable
.
Nothing
def :: letName -> repr a -> repr a Source #
(
let-binds def
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 def :: FromDerived1 (Definable letName) repr => letName -> repr a -> repr a Source #
Instances
(Referenceable letName repr, Eq letName, Hashable letName, Show letName) => Definable letName (FinalizeSharing letName repr) Source # | |
Defined in Symantic.ObserveSharing def :: letName -> FinalizeSharing letName repr a -> FinalizeSharing letName repr a Source # | |
Definable letName (ObserveSharing letName repr) Source # | |
Defined in Symantic.ObserveSharing def :: letName -> ObserveSharing letName repr a -> ObserveSharing letName repr a Source # |
Class MakeLetName
class MakeLetName letName where Source #
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.
forall a. SharingName (StableName a) |
Instances
Eq SharingName Source # | |
Defined in Symantic.ObserveSharing (==) :: SharingName -> SharingName -> Bool # (/=) :: SharingName -> SharingName -> Bool # | |
Hashable SharingName Source # | |
Defined in Symantic.ObserveSharing hashWithSalt :: Int -> SharingName -> Int # hash :: SharingName -> Int # |
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 ObserveSharing
newtype ObserveSharing letName repr a Source #
ObserveSharing | |
|
Instances
observeSharing :: Eq letName => Hashable letName => Show letName => ObserveSharing 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 def
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 ObserveSharingState
data ObserveSharingState letName Source #
ObserveSharingState | |
|
observeSharingNode :: Eq letName => Hashable letName => Show letName => Referenceable letName repr => MakeLetName letName => ObserveSharing letName repr a -> ObserveSharing letName repr a Source #
Type FinalizeSharing
newtype FinalizeSharing letName repr a Source #
FinalizeSharing | |
|
Instances
Class Letsable
class Letsable letName repr where Source #
Nothing
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 (ObserveSharing letName repr) Source # | |
Defined in Symantic.ObserveSharing lets :: LetBindings letName (ObserveSharing letName repr) -> ObserveSharing letName repr a -> ObserveSharing 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