1
1
mirror of https://github.com/github/semantic.git synced 2024-12-03 00:16:52 +03:00

Remove Control.Monad.Effect.Store

This commit is contained in:
joshvera 2018-02-28 15:29:40 -05:00
parent 9aed1b5516
commit 367cfc4f5c

View File

@ -1,34 +0,0 @@
{-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilyDependencies, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Control.Monad.Effect.Store
( assign
, MonadStore(..)
, modifyStore
) where
import Prologue
import Control.Monad.Effect
import Control.Monad.Effect.State
import Data.Abstract.Address
import Data.Abstract.Store
import Data.Abstract.Value
-- | Write a value to the given 'Address' in the 'Store'.
assign :: (Ord (LocationFor a), Semigroup (Cell (LocationFor a) a), Pointed (Cell (LocationFor a)), MonadStore a m) => Address (LocationFor a) a -> a -> m ()
assign address = modifyStore . storeInsert address
-- | 'Monad's offering a readable & writable 'Store' of values for specific 'Address'es.
class Monad m => MonadStore a m where
-- | Get the current store.
getStore :: m (Store (LocationFor a) a)
-- | Update the current store.
putStore :: Store (LocationFor a) a -> m ()
instance (State (Store (LocationFor a) a) :< fs) => MonadStore a (Eff fs) where
getStore = get
putStore = put
-- | Modify the current store using a given function.
modifyStore :: MonadStore a m => (Store (LocationFor a) a -> Store (LocationFor a) a) -> m ()
modifyStore f = getStore >>= putStore . f