Skip to content
Snippets Groups Projects
Commit 748ebf79 authored by sof's avatar sof
Browse files

[project @ 1998-03-20 09:42:30 by sof]

Add Functor instances
parent 99401942
No related merge requests found
......@@ -39,6 +39,14 @@ import PrelGHC
newtype ST s a = ST (PrelST.State s -> (a,PrelST.State s))
instance Functor (ST s) where
map f m = ST $ \ s ->
let
ST m_a = m
(r,new_s) = m_a s
in
(f r,new_s)
instance Monad (ST s) where
return a = ST $ \ s -> (a,s)
......
......@@ -27,6 +27,11 @@ newtype ST s a = ST (State# s -> STret s a)
data STret s a = STret (State# s) a
instance Functor (ST s) where
map f (ST m) = ST $ \ s ->
case (m s) of { STret new_s r ->
STret new_s (f r) }
instance Monad (ST s) where
{-# INLINE return #-}
{-# INLINE (>>) #-}
......
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