Repository : ssh://darcs.haskell.org//srv/darcs/packages/haskeline

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/c3dd85455b1c477966ec8b7b189487fab91fbe0a

>---------------------------------------------------------------

commit c3dd85455b1c477966ec8b7b189487fab91fbe0a
Author: Judah Jacobson <[email protected]>
Date:   Fri May 18 18:20:55 2012 +0000

    Don't make InputT an instance of our internal MonadState/Reader classes.
    
    Haddock displays those instances (which are in actually hidden to the user).
    This makes it seem like InputT implements MonadState/Reader from the mtl
    package.

>---------------------------------------------------------------

 System/Console/Haskeline.hs        |   10 +++++-----
 System/Console/Haskeline/InputT.hs |   16 +++++++++-------
 2 files changed, 14 insertions(+), 12 deletions(-)

diff --git a/System/Console/Haskeline.hs b/System/Console/Haskeline.hs
index 1c1e16d..8894551 100644
--- a/System/Console/Haskeline.hs
+++ b/System/Console/Haskeline.hs
@@ -112,7 +112,7 @@ Unicode characters.
 -- | Write a Unicode string to the user's standard output.
 outputStr :: MonadIO m => String -> InputT m ()
 outputStr xs = do
-    putter <- asks putStrOut
+    putter <- InputT $ asks putStrOut
     liftIO $ putter xs
 
 -- | Write a string to the user's standard output, followed by a newline.
@@ -166,7 +166,7 @@ getInputLineWithInitial prompt (left,right) = promptedInput 
(getInputCmdLine ini
 
 getInputCmdLine :: MonadException m => InsertMode -> TermOps -> String -> 
InputT m (Maybe String)
 getInputCmdLine initialIM tops prefix = do
-    emode <- asks editMode
+    emode <- InputT $ asks editMode
     result <- runInputCmdT tops $ case emode of
                 Emacs -> runCommandLoop tops prefix emacsCommands initialIM
                 Vi -> evalStateT' emptyViState $
@@ -176,8 +176,8 @@ getInputCmdLine initialIM tops prefix = do
 
 maybeAddHistory :: forall m . Monad m => Maybe String -> InputT m ()
 maybeAddHistory result = do
-    settings :: Settings m <- ask
-    histDupes <- asks historyDuplicates
+    settings :: Settings m <- InputT ask
+    histDupes <- InputT $ asks historyDuplicates
     case result of
         Just line | autoAddHistory settings && not (all isSpace line) 
             -> let adder = case histDupes of
@@ -271,7 +271,7 @@ promptedInput doTerm doFile prompt = do
     -- If other parts of the program have written text, make sure that it
     -- appears before we interact with the user on the terminal.
     liftIO $ hFlush stdout
-    rterm <- ask
+    rterm <- InputT ask
     case termOps rterm of
         Right fops -> liftIO $ do
                         putStrOut rterm prompt
diff --git a/System/Console/Haskeline/InputT.hs 
b/System/Console/Haskeline/InputT.hs
index cd100b5..fe203ab 100644
--- a/System/Console/Haskeline/InputT.hs
+++ b/System/Console/Haskeline/InputT.hs
@@ -42,9 +42,11 @@ newtype InputT m a = InputT {unInputT :: ReaderT RunTerm
                                 (StateT History
                                 (StateT KillRing (ReaderT Prefs
                                 (ReaderT (Settings m) m)))) a}
-                            deriving (Monad, MonadIO, MonadException,
-                                MonadState History, MonadReader Prefs,
-                                MonadReader (Settings m), MonadReader RunTerm)
+                            deriving (Monad, MonadIO, MonadException)
+                -- NOTE: we're explicitly *not* making InputT an instance of 
our
+                -- internal MonadState/MonadReader classes.  Otherwise haddock
+                -- displays those instances to the user, and it makes it seem 
like
+                -- we implement the mtl versions of those classes.
 
 instance Monad m => Functor (InputT m) where
     fmap = liftM
@@ -58,15 +60,15 @@ instance MonadTrans InputT where
 
 -- | Get the current line input history.
 getHistory :: Monad m => InputT m History
-getHistory = get
+getHistory = InputT get
 
 -- | Set the line input history.
 putHistory :: Monad m => History -> InputT m ()
-putHistory = put
+putHistory = InputT . put
 
 -- | Change the current line input history.
 modifyHistory :: Monad m => (History -> History) -> InputT m ()
-modifyHistory = modify
+modifyHistory = InputT . modify
 
 -- for internal use only
 type InputCmdT m = StateT Layout (UndoT (StateT HistLog (StateT KillRing
@@ -101,7 +103,7 @@ runInputT = runInputTBehavior defaultBehavior
 
 -- | Returns 'True' if the current session uses terminal-style interaction.  
(See 'Behavior'.)
 haveTerminalUI :: Monad m => InputT m Bool
-haveTerminalUI = asks isTerminalStyle
+haveTerminalUI = InputT $ asks isTerminalStyle
 
 
 {- | Haskeline has two ways of interacting with the user:



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to