{-# LANGUAGE MultiParamTypeClasses,GeneralizedNewtypeDeriving,TypeSynonymInstances,UndecidableInstances,FlexibleContexts,FlexibleInstances #-} -- | some framework to test Editor m w functions, intercepting the console part of the IO module Test where import Control.Monad.State import Control.Monad.Reader import Control.Monad.Error import Control.Monad.Writer import Buffer import Editor import Eval import Operation import Parser import Undo type Line = String [ebuffer,eend] = ["Buffer index error","End"] data Console = Console { cinput :: [Line], coutput :: [Line], cerror :: [Line], chistory:: [Line] } deriving Show type CState = State Console outputT :: String -> CState () outputT x = modify (\y -> y{coutput = x:coutput y}) errorT :: String -> CState () errorT x = modify (\y -> y{cerror = x:cerror y}) historyT x = modify (\y -> y{chistory = x:chistory y}) inputT :: String -> CState (Maybe String) inputT _ = get >>= \y -> let t = cinput y in if null t then return Nothing else put y{cinput = tail t} >> return (Just (head t)) instance SIO CState where inputSio = inputT outputSio = outputT errorSIO = errorT historySio = historyT readfileSio = undefined writefileSio = undefined externalSio = undefined commandhelpSIO = undefined runT is os es hs = execState (run (commandLoop parse eval) zeroState :: CState (Stato InsideAppend)) (Console is os es hs) test is mos mes mhs = let Console _ os es hs = runT is [] [] [] in maybe True (== os) mos && maybe True (== es) mes && maybe True (== hs) mhs loadFile x = readFile x >>= return . ("a" :) . lines