
s> From: Joel Reymont [mailto:joelr1@gmail.com]
How do I run z "a" from ghci or the IO monad?
module Foo where
import qualified Data.Map as M import Control.Monad import Control.Monad.List import Prelude hiding ((!!))
(!!) :: (Ord k, MonadPlus m) => [M.Map k v] -> k -> m v (!!) maps key = msum $ map (M.lookup key) maps x :: M.Map String Int = M.empty y :: M.Map String Int = M.fromList [("a", 1)] z m = [x, y] !! m
There are a couple of ways, depending on how you want to run it through MonadPlus, I think (although I don't understand your code much): main = do let a :: [Int]; a = z "a" print a b <- z "a" print b *Foo> main <<- running main from ghci [1] 1 Or directly the the ghci prompt: *Foo> z "a" *Foo> :t it it :: Int *Foo> print it 1 *Foo> z "a" :: [Int] [1] Did you know about the "it" variable in ghci? It holds the last expression typed at the prompt. Alistair. ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************