{-| Copyright : (c) Hisaket VioletRed, 2022 License : AGPL-3.0-or-later Maintainer : hisaket@outlook.jp Stability : experimental This module provides methods that allow for isolating effects inside or outside the scope locally. It will be useful when using the effects for virtualization or containerization such as libvirt or Docker safely. -} {-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} {-# HLINT ignore "Use camelCase" #-} module Polysemy.Scoped.Path.Isolation where import Polysemy ( Member, Sem, InterpretersFor, Members, rewrite ) import Polysemy.Scoped.Path ( ScopedP, scopedP ) import Polysemy.Input ( Input ) import Polysemy.Bundle ( subsumeBundle, Bundle ) import Control.Category ( (>>>) ) import Polysemy.Scoped.Path.Internal ( bundle, subsumeBundleUsing, unbundle ) import Polysemy.Tagged ( tag, untag, Tagged ) import Polysemy.Membership ( ElemOf ) -- | Variant of 'scopedP' that can isolate effects inside or outside the scope locally. isolatingScopedP :: Member (ScopedP path resource effect) r => path -> InterpretersFor '[Tagged 'Inner effect, Input path, Tagged 'Outer (Bundle r)] r isolatingScopedP = isolatingScopedPSubUsing id -- | Variant of 'scopedP' that can isolate effects inside or outside the scope locally. -- A version that can isolate only a subset of effects in regards to outside the scope. isolatingScopedPSub :: ∀es path resource effect r . (Member (ScopedP path resource effect) r, Members es r) => path -> InterpretersFor '[Tagged 'Inner effect, Input path, Tagged 'Outer (Bundle es)] r isolatingScopedPSub path = untag >>> scopedP path >>> untag >>> subsumeBundle -- | Variant of 'scopedP' that can isolate effects inside or outside the scope locally. isolatingScopedPSubUsing :: ∀es path resource effect r . Member (ScopedP path resource effect) r => (∀e. ElemOf e es -> ElemOf e r) -> path -> InterpretersFor '[Tagged 'Inner effect, Input path, Tagged 'Outer (Bundle es)] r isolatingScopedPSubUsing f path = untag >>> scopedP path >>> untag >>> subsumeBundleUsing f data ScopeSide = Inner -- ^ A tag type that represents effects inside the scope. | Outer -- ^ A tag type that represents effects outside the scope. -- | Isolate only effects inside the scope. inScope :: Member (Tagged Inner (Bundle es)) r => Sem es a -> Sem r a inScope = bundle >>> tag -- | Isolate only effects inside the scope. -- No bundle version. inScope_single :: Member (Tagged Inner eff) r => Sem '[eff] a -> Sem r a inScope_single = bundle >>> rewrite unbundle >>> tag -- | Isolate only effects outside the scope. outScope :: Member (Tagged Outer (Bundle es)) r => Sem es a -> Sem r a outScope = bundle >>> tag