Skip to content
Snippets Groups Projects
Commit 8fca9cba authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 2000-09-05 09:10:22 by simonmar]

Use std monadic operators instead of `thenStrictlyST` and friends.
parent 51afadde
No related merge requests found
...@@ -84,18 +84,18 @@ copyPrefixStr (A# a) len@(I# length#) = ...@@ -84,18 +84,18 @@ copyPrefixStr (A# a) len@(I# length#) =
-- fill in packed string from "addr" -- fill in packed string from "addr"
fill_in ch_array 0# >> fill_in ch_array 0# >>
-- freeze the puppy: -- freeze the puppy:
freeze_ps_array ch_array length# `thenStrictlyST` \ barr -> freeze_ps_array ch_array length# >>= \ barr ->
returnStrictlyST barr ) return barr )
where where
fill_in :: MutableByteArray s Int -> Int# -> ST s () fill_in :: MutableByteArray s Int -> Int# -> ST s ()
fill_in arr_in# idx fill_in arr_in# idx
| idx ==# length# | idx ==# length#
= write_ps_array arr_in# idx (chr# 0#) `seqStrictlyST` = write_ps_array arr_in# idx (chr# 0#) >>
returnStrictlyST () return ()
| otherwise | otherwise
= case (indexCharOffAddr# a idx) of { ch -> = case (indexCharOffAddr# a idx) of { ch ->
write_ps_array arr_in# idx ch `seqStrictlyST` write_ps_array arr_in# idx ch >>
fill_in arr_in# (idx +# 1#) } fill_in arr_in# (idx +# 1#) }
\end{code} \end{code}
...@@ -121,9 +121,9 @@ copySubStrFO (ForeignObj fo) (I# start#) len@(I# length#) = ...@@ -121,9 +121,9 @@ copySubStrFO (ForeignObj fo) (I# start#) len@(I# length#) =
{- allocate an array that will hold the string {- allocate an array that will hold the string
(not forgetting the NUL at the end) (not forgetting the NUL at the end)
-} -}
new_ps_array (length# +# 1#) `thenStrictlyST` \ ch_array -> new_ps_array (length# +# 1#) >>= \ ch_array ->
-- fill in packed string from "addr" -- fill in packed string from "addr"
fill_in ch_array 0# `seqStrictlyST` fill_in ch_array 0# >>
-- freeze the puppy: -- freeze the puppy:
freeze_ps_array ch_array length#) freeze_ps_array ch_array length#)
where where
...@@ -131,11 +131,11 @@ copySubStrFO (ForeignObj fo) (I# start#) len@(I# length#) = ...@@ -131,11 +131,11 @@ copySubStrFO (ForeignObj fo) (I# start#) len@(I# length#) =
fill_in arr_in# idx fill_in arr_in# idx
| idx ==# length# | idx ==# length#
= write_ps_array arr_in# idx (chr# 0#) `seqStrictlyST` = write_ps_array arr_in# idx (chr# 0#) >>
returnStrictlyST () return ()
| otherwise | otherwise
= case (indexCharOffForeignObj# fo (idx +# start#)) of { ch -> = case (indexCharOffForeignObj# fo (idx +# start#)) of { ch ->
write_ps_array arr_in# idx ch `seqStrictlyST` write_ps_array arr_in# idx ch >>
fill_in arr_in# (idx +# 1#) } fill_in arr_in# (idx +# 1#) }
-- step on (char *) pointer by x units. -- step on (char *) pointer by x units.
...@@ -154,9 +154,9 @@ copySubStrBA (ByteArray _ barr#) (I# start#) len@(I# length#) = ...@@ -154,9 +154,9 @@ copySubStrBA (ByteArray _ barr#) (I# start#) len@(I# length#) =
{- allocate an array that will hold the string {- allocate an array that will hold the string
(not forgetting the NUL at the end) (not forgetting the NUL at the end)
-} -}
new_ps_array (length# +# 1#) `thenStrictlyST` \ ch_array -> new_ps_array (length# +# 1#) >>= \ ch_array ->
-- fill in packed string from "addr" -- fill in packed string from "addr"
fill_in ch_array 0# `seqStrictlyST` fill_in ch_array 0# >>
-- freeze the puppy: -- freeze the puppy:
freeze_ps_array ch_array length#) freeze_ps_array ch_array length#)
where where
...@@ -164,13 +164,12 @@ copySubStrBA (ByteArray _ barr#) (I# start#) len@(I# length#) = ...@@ -164,13 +164,12 @@ copySubStrBA (ByteArray _ barr#) (I# start#) len@(I# length#) =
fill_in arr_in# idx fill_in arr_in# idx
| idx ==# length# | idx ==# length#
= write_ps_array arr_in# idx (chr# 0#) `seqStrictlyST` = write_ps_array arr_in# idx (chr# 0#) >>
returnStrictlyST () return ()
| otherwise | otherwise
= case (indexCharArray# barr# (start# +# idx)) of { ch -> = case (indexCharArray# barr# (start# +# idx)) of { ch ->
write_ps_array arr_in# idx ch `seqStrictlyST` write_ps_array arr_in# idx ch >>
fill_in arr_in# (idx +# 1#) } fill_in arr_in# (idx +# 1#) }
\end{code} \end{code}
(Very :-) ``Specialised'' versions of some CharArray things... (Very :-) ``Specialised'' versions of some CharArray things...
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment