| Copyright | (c) John Maraist 2022 |
|---|---|
| License | AllRightsReserved |
| Maintainer | haskell-tms@maraist.org |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
Data.TMS.MList
Description
Unless required by applicable law or agreed to in writing, software distributed under the License is distributed on an "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied, for NON-COMMERCIAL use. See the License for the specific language governing permissions and limitations under the License.
Synopsis
- data MList s a
- toMList :: Monad m => [a] -> STT s m (MList s a)
- showM :: (Show a, Monad m) => MList s a -> STT s m String
- mnull :: MList s a -> Bool
- getMnull :: Monad m => STRef s (MList s a) -> STT s m Bool
- mcar :: forall (m :: Type -> Type) s a. Applicative m => MList s a -> STT s m a
- mcdr :: forall (m :: Type -> Type) s a. Applicative m => MList s a -> STT s m (MList s a)
- mlength :: Monad m => MList s a -> STT s m Int
- fromList :: Monad m => [a] -> STT s m (MList s a)
- fromListMap :: Monad m => (a -> b) -> [a] -> STT s m (MList s b)
- toList :: Monad m => MList s a -> STT s m [a]
- toUnmaybeList :: Monad m => MList s (Maybe a) -> STT s m [a]
- mlistMap :: Monad m => (a -> b) -> MList s a -> STT s m (MList s b)
- mlistFilter :: Monad m => (a -> Bool) -> MList s a -> STT s m (MList s a)
- mlistUnmaybe :: Monad m => MList s (Maybe a) -> STT s m (MList s a)
- mlistStripNothing :: Monad m => MList s (Maybe a) -> STT s m (MList s (Maybe a))
- getMlistStripNothing :: Monad m => STRef s (MList s (Maybe a)) -> STT s m (MList s (Maybe a))
- mlistPush :: Monad m => a -> MList s a -> STT s m (MList s a)
- mlistRefPush :: Monad m => a -> STRef s (MList s a) -> STT s m ()
- mlistFor_ :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> MList s a -> (a -> m ()) -> m ()
- mlistForCons_ :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> MList s a -> (MList s a -> m ()) -> m ()
- mlistForConsWhile_ :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> MList s a -> m Bool -> (MList s a -> m ()) -> m ()
- rplaca :: Monad m => MList s a -> a -> STT s m ()
Mutable lists (cons cells) in STT
Singly linked lists! But with mutable CARs and CDRs à la Common Lisp.
mcar :: forall (m :: Type -> Type) s a. Applicative m => MList s a -> STT s m a Source #
Returns the CAR (element) of the first CONS cell of a non-empty mutable list.
mcdr :: forall (m :: Type -> Type) s a. Applicative m => MList s a -> STT s m (MList s a) Source #
Returns the CDR (next cell) of the first CONS cell of a non-empty mutable list.
mlength :: Monad m => MList s a -> STT s m Int Source #
Convert a traditional Haskell list into a mutable MList list.
fromList :: Monad m => [a] -> STT s m (MList s a) Source #
Convert a traditional Haskell list into a mutable MList list.
fromListMap :: Monad m => (a -> b) -> [a] -> STT s m (MList s b) Source #
Convert a traditional Haskell list into a mutable MList list,
applying the given function to each element.
toList :: Monad m => MList s a -> STT s m [a] Source #
Convert a mutable MList list into a traditional Haskell list.
mlistMap :: Monad m => (a -> b) -> MList s a -> STT s m (MList s b) Source #
A version of map for MLists.
mlistFilter :: Monad m => (a -> Bool) -> MList s a -> STT s m (MList s a) Source #
A version of filter for MLists.
getMlistStripNothing :: Monad m => STRef s (MList s (Maybe a)) -> STT s m (MList s (Maybe a)) Source #
mlistPush :: Monad m => a -> MList s a -> STT s m (MList s a) Source #
Treating an MList as a stack, add a new element at the top of
the stack, and return the new stack top.
mlistRefPush :: Monad m => a -> STRef s (MList s a) -> STT s m () Source #
Treating an MList as a stack, add a new element at the top of
the stack, and return the new stack top.
mlistFor_ :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> MList s a -> (a -> m ()) -> m () Source #
Iterate over the elements of a MList. The body does not
necessarily need operate in the same monad as where the references
originate; the lifter parameter brings the latter into the
former.
mlistForCons_ :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> MList s a -> (MList s a -> m ()) -> m () Source #
mlistForConsWhile_ :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> MList s a -> m Bool -> (MList s a -> m ()) -> m () Source #
A combination of mlistForCons_ and
forMwhile_: iterate over the MCons cell of a
list, with a trigger for an early exit. Note that the monad for
the continuation condition is over the overall monad m, not the
STT wrapped monad m0.