Generating random strings from a string-pool using QuickCheck - haskell

Consider the problem of generating strings out our a set of possible strings, in such a way that once a string is chosen, it cannot be repeated again. For this task I would like to use QuickCheck's Gen functions.
If I look at the type of the function I'm trying to write, it looks pretty much like a state monad. Since I'm using another monad, namely Gen , inside the state monad. I wrote my first attempt using StateT.
arbitraryStringS :: StateT GenState Gen String
arbitraryStringS =
mapStateT stringGenS get
where:
newtype GenState = St {getStrings :: [String]}
deriving (Show)
removeString :: String -> GenState -> GenState
removeString str (St xs) = St $ delete str xs
stringGenS :: Gen (a, GenState) -> Gen (String, GenState)
stringGenS genStSt =
genStSt >>= \(_, st) ->
elements (getStrings st) >>= \str ->
return (str, removeString str st)
Something that troubles me about this implementation is the fact that I'm not using the first element of stringGenS. Secondly, my end goal is to define a random generator for JSON values, that make use of a resource pool (which contains not only strings). Using StateT led me to implement "stateful" variants of QuickCheck's elements, listOf, etc.
I was wondering whether there's a better way of achieving this, or such a complexity is inherent to defining stateful variants of existing monads.

The combination of StateT and Gen could look like this:
import Control.Monad.State
import Data.List (delete)
import Test.QuickCheck
-- A more efficient solution would be to use Data.Set.
-- Even better, Data.Trie and ByteStrings:
-- https://hackage.haskell.org/package/bytestring-trie-0.2.4.1/docs/Data-Trie.html
newtype GenState = St { getStrings :: [String] }
deriving (Show)
removeString :: String -> GenState -> GenState
removeString str (St xs) = St $ delete str xs
stringGenS :: StateT GenState Gen String
stringGenS = do
s <- get
str <- lift $ elements (getStrings s)
modify $ removeString str
return str
The problem is that as you need the state, you can't run multiple such computations in Gen while sharing the state. The only reasonable thing to do would be to generate multiple random unique strings together (using the same state) as
evalStateT (replicateM 10 stringGenS)
which is of type GenState -> Gen [String].

Related

Haskell UUID generation

I am new to Haskell and need help. I am trying to build a new data type that has to be somehow unique, so I decided to use UUID as a unique identifier:
data MyType = MyType {
uuid :: UUID,
elements :: AnotherType
}
in this way, I can do following:
instance Eq MyType where
x == y = uuid x == uuid y
x /= y = not (x == y)
The problem is that all known (to me) UUID generators produce IO UUID, but I need to use it in a pure code as mentioned above. Could you please suggest if there is any way to extract UUID out of IO UUID, or maybe be there is a better way to do what I need in Haskell? Thanks.
UPDATE
Thanks for all the great suggestions and the code example. From what is posted here I can say you cannot break a referential transparency, but there are smart ways how to solve the problem without breaking it and, probably the most optimal one, is listed in the answer below.
There is also one alternative approach that I was able to explore myself based on provided recommendations with the usage of State Monad:
type M = State StdGen
type AnotherType = String
data MyType = MyType {
uuid :: UUID,
elements :: AnotherType
} deriving (Show)
mytype :: AnotherType -> M MyType
mytype x = do
gen <- get
let (val, gen') = random gen
put gen'
return $ MyType val x
main :: IO ()
main = do
state <- getStdGen
let (result, newState) = runState (mytype "Foo") state
putStrLn $ show result
let (result', newState') = runState (mytype "Bar") newState
setStdGen newState'
putStrLn $ show result'
Not sure if it is the most elegant implementation, but it works.
If you're looking at the functions in the uuid package, then UUID has a Random instance. This means that it's possible to generate a sequence of random UUIDs in pure code using standard functions from System.Random using a seed:
import System.Random
import Data.UUID
someUUIDs :: [UUID]
someUUIDs =
let seed = 123
g0 = mkStdGen seed -- RNG from seed
(u1, g1) = random g0
(u2, g2) = random g1
(u3, g3) = random g2
in [u1,u2,u3]
Note that someUUIDs creates the same three "unique" UUIDs every time it's called because the seed is hard-coded.
As with all pure Haskell code, unless you cheat (using unsafe functions), you can't expect to generate a sequence of actually unique UUIDs without explicitly passing some state (in this case, a StdGen RNG) between calls to random.
The usual solution to avoid the ugly boilerplate of passing the generator around is to run at least part of your code within a monad that can maintain the needed state. Some people like to use the MonadRandom package, though you can also use the regular State monad with a StdGen somewhere in the state. The main advantages of MonadRandom over State is that you get some dedicated syntax (getRandom) and can create a monad stack that includes both RandomT and StateT so you can separate your RNG state from the rest of your application state.
Using MonadRandom, you might write an application like:
import Control.Monad.Random.Strict
import System.Random
import Data.UUID
-- monad for the application
type M = Rand StdGen
-- get a generator and run the application in "M"
main :: IO ()
main = do
g <- getStdGen -- get a timestamp-seeded generator
let log = evalRand app g -- run the (pure) application in the monad
putStr log
-- the "pure" application, running in monad "M"
app :: M String
app = do
foo <- myType "foo"
bar <- myType "bar"
-- do some processing
return $ unlines ["Results:", show foo, show bar]
type AnotherType = String
data MyType = MyType {
uuid :: UUID,
elements :: AnotherType
} deriving (Show)
-- smart constructor for MyType with unique UUID
myType :: AnotherType -> M MyType
myType x = MyType <$> getRandom <*> pure x
Note that substantial parts of the application will need to be written in monadic syntax and run in the application M monad. This isn't a big restriction -- most non-trivial applications are going to be written in some monad.

How to work with mutable structures in the IO monad

TL;DR:
How do I ensure persistence of values generated by randomRIO (from System.Random) within a given do statement?
How do I work with mutable structures in the IO Monad?
My initial question was (so very) wrong - I'm updating the title so future readers who want to understand use mutable structures in the IO monad can find this post.
Longer version:
A heads up:
This looks long but a lot of it is just me giving an overview of how exercism.io works. (UPDATE: the last two code-blocks are older versions of my code which are included as reference, in case future readers would like to follow along with the iterations in the code based on the comments/answers.)
Overview of Exercise:
I'm working on the Robot Name exercise from (the extremely instructive) exercism.io. The exercise involves creating a Robot data type which is capable of storing a name, which is randomly generated (exercise Readme is included below).
For those who aren't familiar with it, the exercism.io learning model is based on automated testing of student-generated code. Each exercise consists of a series of tests (written by the test author) and the solution code must be able to pass all of them. Our code must pass all tests in a given exercise's test file, before we can move to the next exercise - an effective model, imo. (Robot Name is exercise #20 or so.)
In this particular exercise, we're asked to create a Robot data-type and three accompanying functions: mkRobot, robotName and resetName.
mkRobot generates an instance of a Robot
robotName generates and "returns" a unique name for a unnamed Robot (i.e., robotName does not overwrite a pre-existing name); if a Robot already has a name, it simply "returns" the existing name
resetName overwrites a pre-existing name with a new one.
In this particular exercise, there are 7 tests. The tests checks that:
0) robotName generates names that conforms to the specified pattern (a
name is 5 characters long and is made up of two letters followed by
three digits, e.g., AB123, XQ915, etc.)
1) a name assigned by robotName is persistent (i.e., let's say we create robot A and assign him (or her) a name using robotName; calling robotName a second time (on robot A) shouldn't overwrite his name)
2) robotName generates unique names for different robots (i.e., it tests that we're actually randomizing the process)
3) resetName generates names that conform to the specified pattern (similar to test #0)
4) a name assigned by resetName is persistent
5) resetName assigns a different name (i.e., resetName gives a robot a name that's different form it's current name)
6) resetName affects only one robot at a time (i.e., let's say we have robot A and robot B; resetting robot A's name shouldn't affect robot B's name) AND (ii) names that are generated by resetName are persistent
As reference, here's the test itself: https://github.com/dchaudh/exercism-haskell-solutions/blob/master/robot-name/robot-name_test.hs
Where I'm stuck:
Version 1 (original post): At the moment, my code fails on three tests (#1, #4 and #6) all of which have to do with persistence of a robot's name..
Version 2: (interim) Now my code fails on one test (#5) only - test 5 has to do with changing the name of a robot that we've already created
(thanks to bheklikr for his helpful comments which helped me clean up version 1)
Version 3 (final): The code is now fixed (and passes all tests) thanks to Cirdec's thorough post below. For future reader's benefit, I'm including the final version of the code along with the two earlier versions (so they can follow along with the various comments/answers).
Version 3 (Final):
Here's the final version based on Cirdec's answer below (which I'd highly recommend reading). It turns out that my original question (which asked how to create persistent variables using System.Random) was just totally wrong because my initial implementation was unsound. My question should instead have asked how to work with mutable structures in the IO monad (which Cirdec explains below).
{-# LANGUAGE NoMonomorphismRestriction #-}
module Robot (robotName, mkRobot, resetName) where
import Data.Map (fromList, findWithDefault)
import System.Random (Random, randomRIO)
import Control.Monad (replicateM)
import Data.IORef (IORef, newIORef, modifyIORef, readIORef)
newtype Robot = Robot { name :: String }
mkRobot :: IO (IORef Robot)
mkRobot = mkRobotName >>= return . Robot >>= newIORef
robotName :: IORef Robot -> IO String
robotName rr = readIORef rr >>= return . name
resetName :: IORef Robot -> IO ()
resetName rr = mkRobotName >>=
\newName -> modifyIORef rr (\r -> r {name = newName})
mkRobotName :: IO String
mkRobotName = replicateM 2 getRandLetter >>=
\l -> replicateM 3 getRandNumber >>=
\n -> return $ l ++ n
getRandNumber :: IO Char
getRandNumber = fmap getNumber $ randomRIO (1, 10)
getRandLetter :: IO Char
getRandLetter = fmap getLetter $ randomRIO (1, 26)
getNumber :: Int -> Char
getNumber i = findWithDefault ' ' i alphabet
where alphabet = fromList $ zip [1..] ['0'..'9']
getLetter :: Int -> Char
getLetter i = findWithDefault ' ' i alphabet
where alphabet = fromList $ zip [1..] ['A'..'Z']
Version 2 (Interim):
Based on bheklikr's comments which clean up the mkRobotName function and which help start fixing the mkRobot function. This version of the code yielded an error on test #5 only - test #5 has to do with changing a robot's name, which motivates the need for mutable structures...
{-# LANGUAGE NoMonomorphismRestriction #-}
module Robot (robotName, mkRobot, resetName) where
import Data.Map (fromList, findWithDefault)
import System.Random (Random, randomRIO)
import Control.Monad (replicateM)
data Robot = Robot (IO String)
resetName :: Robot -> IO String
resetName (Robot _) = mkRobotName >>= \name -> return name
mkRobot :: IO Robot
mkRobot = mkRobotName >>= \name -> return (Robot (return name))
robotName :: Robot -> IO String
robotName (Robot name) = name
-------------------------------------------------------------------------
--Supporting functions:
mkRobotName :: IO String
mkRobotName = replicateM 2 getRandLetter >>=
\l -> replicateM 3 getRandNumber >>=
\n -> return $ l ++ n
getRandNumber :: IO Char
getRandNumber = fmap getNumber $ randomRIO (1, 10)
getRandLetter :: IO Char
getRandLetter = fmap getLetter $ randomRIO (1, 26)
getNumber :: Int -> Char
getNumber i = findWithDefault ' ' i alphabet
where alphabet = fromList $ zip [1..] ['0'..'9']
getLetter :: Int -> Char
getLetter i = findWithDefault ' ' i alphabet
where alphabet = fromList $ zip [1..] ['A'..'Z']
Version 1 (Original):
In retrospect, this is laughably bad. This version failed on tests #1, #4 and #6 all of which are related to persistence of a robot's name.
{-# LANGUAGE NoMonomorphismRestriction #-}
module Robot (robotName, mkRobot, resetName) where
import Data.Map (fromList, findWithDefault)
import System.Random (Random, randomRIO)
data Robot = Robot (IO String)
resetName :: Robot -> IO Robot
resetName (Robot _) = return $ (Robot mkRobotName)
mkRobot :: IO Robot
mkRobot = return (Robot mkRobotName)
robotName :: Robot -> IO String
robotName (Robot name) = name
--the mass of code below is used to randomly generate names; it's probably
--possible to do it in way fewer lines. but the crux of the main problem lies
--with the three functions above
mkRobotName :: IO String
mkRobotName = getRandLetter >>=
\l1 -> getRandLetter >>=
\l2 -> getRandNumber >>=
\n1 -> getRandNumber >>=
\n2 -> getRandNumber >>=
\n3 -> return (l1:l2:n1:n2:n3:[])
getRandNumber :: IO Char
getRandNumber = randomRIO (1,10) >>= \i -> return $ getNumber i
getNumber :: Int -> Char
getNumber i = findWithDefault ' ' i alphabet
where alphabet = fromList $ zip [1..] ['0'..'9']
getRandLetter :: IO Char
getRandLetter = randomRIO (1,26) >>= \i -> return $ getLetter i
getLetter :: Int -> Char
getLetter i = findWithDefault ' ' i alphabet
where alphabet = fromList $ zip [1..] ['A'..'Z']
Let's start with the types, based on what is required by the tests. mkRobot returns something in IO
mkRobot :: IO r
robotName takes what is returned from mkRobot and returns an IO String.
robotName :: r -> IO String
Finally, resetName takes what is returned from mkRobot and produces an IO action. The return of this action is never used, so we'll use the unit type () for it which is normal for IO actions with no result in Hasekll.
resetName :: r -> IO ()
Based on the tests, whatever r is needs to be able to behave like it is mutated by resetName. We have a number of options for things that behave like they are mutable in IO: IORefs, STRefs, MVarss, and software transactional memory. My go-to preference for simple problems is the IORef. I'm going to take a slightly different tack than you, and separate the IORef from what a Robot is.
newtype Robot = Robot {name :: String}
This leaves Robot a very pure data type. Then I'll use IORef Robot for what r is in the interface to the tests.
IORefs provide five extremely useful functions for working with them, which we will use three of. newIORef :: a -> IO (IORef a) makes a new IORef holding the provided value. readIORef :: IORef a -> IO a reads the value stored in the IORef. modifyIORef :: IORef a -> (a -> a) -> IO () applies the function to the value stored in the IORef. There are two other extremely useful functions we won't use, writeIORef which sets the value without looking at what's there, and atomicModifyIORef which solves about half of the shared memory problems in writing multi-threaded programs. We'll import the three that we will use
import Data.IORef (IORef, newIORef, modifyIORef, readIORef)
When we make a new Robot we'll be making a new IORef Robot with newIORef.
mkRobot :: IO (IORef Robot)
mkRobot = mkRobotName >>= return . Robot >>= newIORef
When we read the name, we'll read the Robot with readIORef, then return the Robot's name
robotName :: IORef Robot -> IO String
robotName rr = readIORef rr >>= return . name
Finally, resetName will mutate the IORef. We'll make a new name for the robot with mkRobotName, then call modifyIORef with a function that sets the robot's name to the new name`.
resetName :: IORef Robot -> IO ()
resetName rr = mkRobotName >>=
\newName -> modifyIORef rr (\r -> r {name = newName})
The function \r -> r {name = newName} is the same as const (Robot newName), except that it will only change the name if we later decide to add some other field to the Robot data type.

How can I unpack an arbitrary length list of IO Bool

I'm writing a program that should be able to simulate many instances of trying the martingale betting system with roulette. I would like main to take an argument giving the number of tests to perform, perform the test that many times, and then print the number of wins divided by the total number of tests. My problem is that instead of ending up with a list of Bool that I could filter over to count successes, I have a list of IO Bool and I don't understand how I can filter over that.
Here's the source code:
-- file: Martingale.hs
-- a program to simulate the martingale doubling system
import System.Random (randomR, newStdGen, StdGen)
import System.Environment (getArgs)
red = [1,3,5,7,9,12,14,16,18,19,21,23,25,27,30,32,34,36]
martingale :: IO StdGen -> IO Bool
martingale ioGen = do
gen <- ioGen
return $ martingale' 1 0 gen
martingale' :: Real a => a -> a -> StdGen -> Bool
martingale' bet acc gen
| acc >= 5 = True
| acc <= -100 = False
| otherwise = do
let (randNumber, newGen) = randomR (0,37) gen :: (Int, StdGen)
if randNumber `elem` red
then martingale' 1 (acc + bet) newGen
else martingale' (bet * 2) (acc - bet) newGen
main :: IO ()
main = do
args <- getArgs
let iters = read $ head args
gens = replicate iters newStdGen
results = map martingale gens
--results = map (<-) results
print "THIS IS A STUB"
Like I have in my comments, I basically want to map (<-) over my list of IO Bool, but as I understand it, (<-) isn't actually a function but a keyword. Any help would be greatly appreciated.
map martingale gens will give you something of type [IO Bool]. You can then use sequence to unpack it:
sequence :: Monad m => [m a] -> m [a]
A more natural alternative is to use mapM directly:
mapM :: Monad m => (a -> m b) -> [a] -> m [b]
i.e. you can write
results <- mapM martingale gens
Note - even after doing it this way, your code feels a bit unnatural. I can see some advantages to the structure, in particular because martingale' is a pure function. However having something of type IO StdGen -> IO Bool seems a bit odd.
I can see a couple of ways to improve it:
make martingale' return an IO type itself and push the newStdGen call all the way down into it
make gens use replicateM rather than replicate
You may want to head over to http://codereview.stackexchange.com for more comprehensive feedback.

Using a random number to encrypt a message

I'm currently trying to encrypt a message (String) with the help of a random generated number in Haskell. The idea is to get the message, generate a random String of numbers with the same length (or more and then to take the length I need).
Then i want to perform some actions based on the ASCII representation and then return the encrypted String.
Unfortunately I'm not very versed with monads in Haskell, so it might be a very simple problem to solve, which I can't comprehend yet.
generateMyKey string = newStdGen >>= \x -> print $ concatMap show $ map abs $ rs x
where rs x = randomlist (length string) x
randomlist :: Int -> StdGen -> [Int]
randomlist n = take n . unfoldr (Just . random)
So the problem is I get an IO() out of getMyKey, but I want to have a String, or atleast a IO(String) to perform the encrypting mechanism.
Right now I'm getting a big list of positive (hence the abs + map) random numbers, but I can't access them.
There are two basic ways to go about this (and one more complicated but easier). If you're just using System.Random, you can generate random numbers in two ways, either by accepting a StdGen and staying pure, or using the OS's random generator and staying in IO. At some point, you'll have to make a call to the OS's random functionality to get a seed or value, but this can happen in main far away from your actual code.
To keep your functions pure, you'll need to pass around a StdGen and use the functions
random :: Random a => StdGen -> (a, StdGen)
randoms :: Random a => StdGen -> [a]
(Note: I've substituted RandomGen g => g for StdGen, there's no need to write a custom RandomGen instance for your case)
You can then write your function generateMyKey as
randomList :: Int -> StdGen -> [Int]
randomList n = take n . randoms
generateMyKey :: String -> StdGen -> String
generateMyKey text g
= concatMap show
$ map abs
$ randomList (length text) g
And this entirely avoids having to live in IO. Be wary, though, if you re-use the same g, you'll generate the same random list each time. We can avoid this by using IO and its related functions
randomList :: Int -> IO [Int]
randomList 0 = return []
randomList n = do
first <- randomIO
rest <- randomList (n - 1) -- Recursively generate the rest
return $ first : rest
generateMyKey :: String -> IO String
generateMyKey text = do
key <- randomList (length text)
return $ concatMap show $ map abs $ key
This will come with a performance hit, and now we've lost the ability to generate the same key repeatedly, making it difficult to test our functions reliably! How can we reconcile these two approaches?
Enter the package MonadRandom. This package provides a monad (and monad transformer, but you don't need to worry about that right now) that lets you abstract away how you generate random numbers so that you can choose how you want to run your code in different circumstances. If you want IO, you can use IO. If you want to supply a seed, you can supply a seed. It's very handy. You can install it with cabal install MonadRandom and use it as
import Control.Monad.Random
randomList :: Int -> Rand StdGen [Int]
randomList n = fmap (take n) getRandoms
generateMyKey :: String -> Rand StdGen String
generateMyKey text = do
key <- randomList (length text)
return $ concatMap show $ map abs $ key
Our generateMyKey code is even the same as the IO version other than the type signature!
Now to run it.
main :: IO ()
main = do
-- Entirely impure, have it automatically grab a StdGen from IO for us
ioVersion <- evalRandIO $ generateMyKey "password"
-- Make a StdGen that stays the same every time we run the program, useful for testing
let pureStdGen = mkStdGen 12345
pureVersion = evalRand (generateMyKey "password") pureStdGen
-- Get a StdGen from the system, but still evaluate it purely
ioStdGen <- getStdGen
let pureVersion2 = evalRand (generateMyKey "password") ioStdGen
-- Print out all three versions
putStrLn ioVersion
putStrLn pureVersion
putStrLn pureVersion2
There are a number of solutions to this problem, but at first glance it might seem that you need to have your entire program operate in the IO monad, but you don't! The entry (/exit) point of your program is the only place that needs to see IO -- you can factor out any transformations on your random list into pure functions, i.e:
import Data.List
import System.Random
generateMyKey :: String -> IO String
generateMyKey string = do
x <- newStdGen
let rs = randomlist (length string)
return $ concatMap show $ map abs $ rs x
randomlist :: Int -> StdGen -> [Int]
randomlist n = take n . unfoldr (Just . random)
change :: String -> String
change = reverse -- for example
main :: IO ()
main = do
key <- generateMyKey "what"
putStrLn $ change key
generateMyKey is identical to what you had before, except that it's written in do notation now and is returning the string instead of just printing it. This allows us to "pull out" a random key from inside the IO monad and transform it with regular pure functions, like change, for example. This allows you to reason about the pure functions as normal, while still pulling in your values from IO.

"Persistently" Impure (IO) Vectors in Haskell, with database-like persistent interface

I have a computation that is best described as iterative mutations on a vector; the final result is the final state of the vector.
The "idiomatic" approach to making this functional, I think, is to simply pass on a new vector object along whenever it is "modified". So your iterative method would be operate_on_vector :: Vector -> Vector, which takes in a vector and outputs the modified vector, which is then fed through the method again.
This method is pretty straightforward and I had no problems implementing it, even being new to Haskell.
Alternatively, one could encapsulate all of this in a State monad and pass along a constantly re-created and modified vector as the state value.
However, I suffer a huge, huge performance cost, as these calculations are pretty intensive, the iterations many (on the order of millions) and the data vectors can get pretty large (on the order of at least thousands of primitives). Re-creating a new vector in memory at every step of the iteration seems pretty costly, data collection or not.
Then I considered how IO works -- it can be seen as basically like State, except the state value is the "World", which is constantly changing.
Maybe I could use something that is like IO to "operate" on a "world"? And the "world" would be the vector in-memory? Sort of like a database query, but everything is in memory.
For example with io you could do
do
putStrLn "enter something"
something <- getLine
putStrLine $ "you entered " ++ something
which can be seen as "performing" putStrLn and "modifying" the World object, returning a new World object and feeding it into the next function, which queryies the world object for a string that is the result of the modification, and then returns another world object after another modification.
Is there anything like that that can do this for mutable vectors?
do
putInVec 0 9 -- index 0, value 9
val <- getFromVec 0
putInVec 0 (val + 1)
, with "impure" "mutable" vectors, instead of passing along a new modified vector at each step.
I believe you can do this using mutable vector and a thin wrapper over Reader + ST (or IO) monad.
It can look like this:
type MyVector = IOVector $x -- Use your own elements type here instead of $x
newtype VectorIO a = VectorIO (ReaderT MyVector IO a) deriving (Monad, MonadReader, MonadIO)
-- You will need GeneralizedNewtypeDeriving extension here
-- Run your computation over an existing vector
runComputation :: MyVector -> VectorIO a -> IO MyVector
runComputation vector (VectorIO action) = runReaderT action vector >> return vector
-- Run your computation over a new vector of the specified length
runNewComputation :: Int -> VectorIO a -> IO MyVector
runNewComputation n action = do
vector <- new n
runComputation vector action
putInVec :: Int -> $x -> VectorIO ()
putInVec idx val = do
v <- ask
liftIO $ write v idx val
getFromVec :: Int -> VectorIO $x
getFromVec idx = do
v <- ask
liftIO $ read v idx
That's really all. You can use VectorIO monad to perform your computations, just like you wanted in your example. If you do not want IO but want pure computations, you can use ST monad; modifications to the code above will be trivial.
Update
Here is an ST-based version:
{-# LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances, MultiParamTypeClasses, Rank2Types #-}
module Main where
import Control.Monad
import Control.Monad.Trans.Class
import Control.Monad.Reader
import Control.Monad.Reader.Class
import Control.Monad.ST
import Data.Vector as V
import Data.Vector.Mutable as MV
-- Your type of the elements
type E = Int
-- Mutable vector which will be used as a context
type MyVector s = MV.STVector s E
-- Immutable vector compatible with MyVector in its type
type MyPureVector = V.Vector E
-- Simple monad stack consisting of a reader with the mutable vector as a context
-- and of an ST action
newtype VectorST s a = VectorST (ReaderT (MyVector s) (ST s) a) deriving Monad
-- Make the VectorST a reader monad
instance MonadReader (MyVector s) (VectorST s) where
ask = VectorST $ ask
local f (VectorST a) = VectorST $ local f a
reader = VectorST . reader
-- Lift an ST action to a VectorST action
liftST :: ST s a -> VectorST s a
liftST = VectorST . lift
-- Run your computation over an existing vector
runComputation :: MyVector s -> VectorST s a -> ST s (MyVector s)
runComputation vector (VectorST action) = runReaderT action vector >> return vector
-- Run your computation over a new vector of the specified length
runNewComputation :: Int -> VectorST s a -> ST s (MyVector s)
runNewComputation n action = do
vector <- MV.new n
runComputation vector action
-- Run a computation on a new mutable vector and then freeze it to an immutable one
runComputationPure :: Int -> (forall s. VectorST s a) -> MyPureVector
runComputationPure n action = runST $ do
vector <- runNewComputation n action
V.unsafeFreeze vector
-- Put an element into the current vector
putInVec :: Int -> E -> VectorST s ()
putInVec idx val = do
v <- ask
liftST $ MV.write v idx val
-- Retrieve an element from the current vector
getFromVec :: Int -> VectorST s E
getFromVec idx = do
v <- ask
liftST $ MV.read v idx

Resources