[haskeline] #132: MonadTrans instance is not exported

haskeline haskeline at projects.haskell.org
Thu May 29 06:53:11 BST 2014


#132: MonadTrans instance is not exported
-------------------+--------------------------------------------------------
Reporter:  m09     |       Owner:     
    Type:  defect  |      Status:  new
Priority:  major   |   Milestone:     
 Version:          |    Keywords:     
-------------------+--------------------------------------------------------
 Which mean it's impossible to easily embed IO actions in the InputT m
 Monad:


 {{{
 {-# LANGUAGE UnicodeSyntax #-}

 import           Control.Monad.Trans
 import           Data.Array.IO
 import           System.Console.Haskeline

 type Board = IOArray Int Int

 problem ∷ Board → IO Int
 problem board = runInputT defaultSettings . lift $ readArray board 1

 main ∷ IO ()
 main = (newArray (0, 3) 42 ∷ IO Board) >> return ()

 -- [1 of 1] Compiling Main             ( main.hs, main.o )
 --
 -- main.hs:13:7:
 --     No instance for (MonadTrans InputT) arising from a use of `lift'
 --     Possible fix: add an instance declaration for (MonadTrans InputT)
 --     In the expression: lift
 --     In a stmt of a 'do' block: lift $ readArray board 1
 --     In the expression: do { lift $ readArray board 1 }
 }}}

-- 
Ticket URL: <http://trac.haskell.org/haskeline/ticket/132>
haskeline <http://example.org/>
My example project


More information about the Haskeline mailing list