Skip to content

Commit

Permalink
Fix tweag#404: add evalState(T)
Browse files Browse the repository at this point in the history
Use case: stateful interpreter (`eval`) for C-like expressions `e`:
```haskell
let Ur value = HashMap.empty capacity (\ env -> move (evalState (eval e) env))
```
This pattern breaks the "jail" set by the type signature of
`HashMap`-allocation:
```haskell
empty :: Int -> (HashMap k v %1 -> Ur b) %1 -> Ur b
```
`HashMap` is not `Movable` but `Consumable`, so we can get rid of it before
`move`ing the result to `Ur`.
  • Loading branch information
andreasabel committed Apr 12, 2022
1 parent d84384b commit d15b300
Show file tree
Hide file tree
Showing 3 changed files with 16 additions and 1 deletion.
2 changes: 2 additions & 0 deletions src/Control/Functor/Linear.hs
Original file line number Diff line number Diff line change
Expand Up @@ -48,11 +48,13 @@ module Control.Functor.Linear
State,
state,
runState,
evalState,
execState,
mapState,
withState,
StateT (..),
runStateT,
evalStateT,
execStateT,
mapStateT,
withStateT,
Expand Down
13 changes: 13 additions & 0 deletions src/Control/Functor/Linear/Internal/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,8 @@ module Control.Functor.Linear.Internal.State
runState,
mapStateT,
mapState,
evalStateT,
evalState,
execStateT,
execState,
withStateT,
Expand All @@ -36,6 +38,7 @@ import qualified Control.Monad.Trans.State.Strict as NonLinear
import Data.Functor.Identity
import qualified Data.Functor.Linear.Internal.Applicative as Data
import qualified Data.Functor.Linear.Internal.Functor as Data
import qualified Data.Tuple.Linear as Linear
import Data.Unrestricted.Linear.Internal.Consumable
import Data.Unrestricted.Linear.Internal.Dupable
import Prelude.Linear.Internal
Expand Down Expand Up @@ -80,6 +83,11 @@ withStateT r (StateT f) = StateT (f . r)
execStateT :: Functor m => StateT s m () %1 -> s %1 -> m s
execStateT f = fmap (\((), s) -> s) . (runStateT f)

-- | Use with care!
-- This consumes the final state, so might be costly at runtime.
evalStateT :: (Functor m, Consumable s) => StateT s m a %1 -> s %1 -> m a
evalStateT f = fmap Linear.fst . runStateT f

mapState :: ((a, s) %1 -> (b, s)) %1 -> State s a %1 -> State s b
mapState f = mapStateT (Identity . f . runIdentity')

Expand All @@ -89,6 +97,11 @@ withState = withStateT
execState :: State s () %1 -> s %1 -> s
execState f = runIdentity' . execStateT f

-- | Use with care!
-- This consumes the final state, so might be costly at runtime.
evalState :: Consumable s => State s a %1 -> s %1 -> a
evalState f = runIdentity' . evalStateT f

modify :: Applicative m => (s %1 -> s) %1 -> StateT s m ()
modify f = state $ \s -> ((), f s)

Expand Down
2 changes: 1 addition & 1 deletion src/Data/Tuple/Linear.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ module Data.Tuple.Linear
where

import Data.Unrestricted.Linear.Internal.Consumable
import Prelude.Linear.Internal ( curry, uncurry )
import Prelude.Linear.Internal (curry, uncurry)

fst :: Consumable b => (a, b) %1 -> a
fst (a, b) = lseq b a
Expand Down

0 comments on commit d15b300

Please sign in to comment.