{-# LANGUAGE MultiParamTypeClasses,NoMonomorphismRestriction,FlexibleContexts,FlexibleInstances,UndecidableInstances #-} -- | Main datas and types for the editor module Editor where import Control.Monad.State import Control.Monad.Reader import Control.Monad.Error import Undo import Engine -- | Stato is parametrized on an Engine instance and hold the engine with the last regex entered , regex G and g are not implemented now data Stato w = Stato { file :: w, -- ^ data holding the file lastre :: String, -- ^ a regex filename :: Maybe String, -- ^ the file we are editing pending :: Maybe Command, -- ^ a sensible state for data lost lastsaved :: Maybe w } deriving (Show,Eq) zeroState = Stato empty "" Nothing Nothing Nothing -- | the core editor runs under the state monad with state (Stato w) . -- Wrapped around a monad (IO mainly) to permit console input and output of commands with IO -- and testing with State type StatoE m w = UndoT (Stato w) m liftStatoE :: Ctx m w => StatoE m w a -> Editor m w a liftStatoE = lift -- | push a new file (data 'Engine' instance) in the core State, pushing the old state in the undo stack hputfile :: Ctx m w => w -> Editor m w () hputfile x = get >>= \y -> liftStatoE $ hput y {file = x} putfile x = get >>= \y -> put y {file = x} putlastre x = get >>= \y -> put y {lastre = x} setfilename x = get >>= \y -> put y {filename = x} setpending x = get >>= \y -> put y {pending = x} setlastsaved = get >>= \y -> put y {lastsaved = Just (file y)} unsetlastsaved = get >>= \y -> put y {lastsaved = Nothing} -- | placeholder for the two constraints class (Engine w , SIO m, HCtx m (Stato w) ) => Ctx m w instance (Engine w , SIO m, HCtx m (Stato w) ) => Ctx m w -- | the errors (monad failers) which can break the monad flow data Err = StopErr -- ^ issued on ctrl-d or q command (q not implemented) | ParserErr String -- ^ command line was not parsed to a CompleteCommand | RegexUnmatched -- ^ the regex doesn't match a line | EvalErr Err -- ^ something bad happened in the evaluation process | BackendErr -- ^ lines were addressed out of file (see 'Engine') | Ahi String -- ^ uncontrolled errors | FileReadErr String -- ^ io error trying to load a file | FileNameMissing -- ^ filename is not set | FileWriteErr String -- ^ io error trying to write the file | ExternalCommandErr String -- ^ io error executing an external program | PendingState Command -- ^ a sensible data discarding command has been entered | NoMoreUndo -- ^ reached the first state remembered | NoMoreRedo -- ^ reached the last state remembered | CommandHelpMissing -- ^ a help for a missing command was asked | CommandHelpParseErr String -- ^ error parsing the help for commands deriving Show instance Error Err where noMsg = Ahi "nomsg" strMsg = Ahi -- | a layer for IO simulation, see "Main" for the real program one and "Test" for tests class (Monad m) => SIO m where -- | accepts a prompt and should return Nothing on eof else a line of input inputSio :: String -> m (Maybe String) outputSio :: String -> m () -- ^ output a normal string historySio :: String -> m () -- ^ put a line in the history (which is global) errorSIO :: String -> m () -- ^ output an error string readfileSio :: String -> ErrorT String m String -- ^ read a file writefileSio :: String -> String -> ErrorT String m () -- ^ write a file -- | runs an external command , first arg is the command -- the output is returned or an error is signalled in the errort monad externalSio :: String -> ErrorT String m String -- the path for the command help file commandhelpSIO :: m FilePath liftSio :: Ctx m w => m a -> Editor m w a liftSio = lift . lift -- | commands for the editor data Command -- | get some text and add it after the addressed line = Append -- | get some text and add it before the addressed line | Insert -- | get some text and add it in place of some deleted lines | Change -- | delete some lines | Delete -- | print some lines | Print -- | get some commands and execute them on each line matching a regex | SmallG String -- not implemented -- | interactively execute commands on each line matching a regex | BigG String -- not implemented -- | Change the addressed line | NoCommand -- | Load a file | Edit String -- | Write the file | Write -- | Write a new file | WriteNew String -- | Set filename | SetFilename String -- | Print filename | GetFilename -- | Load the output of an external command | EditExternal String -- | Revert the last change if ever | UndoChange -- | Restore via the last change | RedoChange -- | Asking help | HelpList -- | Spedific help | HelpTopic String deriving (Show,Eq) -- | represents a line position in the file data Offset -- | beyond last line, the append line = LastLine -- | the nth line | Absolute Int -- | the line addressed by the engine | Current -- | the nth line before the addressed one | Prev Int -- | the nth line aftor the addressed one | Next Int -- | the next line (wrapping around) matching a regex | ReNext String -- | the next line matching the last learned regex | LastReNext -- | the previous line (wrapping around) matching a regex | RePrev String -- | the previous matching the last learned regex | LastRePrev -- | the line marked previously with a char | MarkedAs Char deriving Show -- | a couple of Offsets data Range = Range Offset Offset deriving Show -- | wrapper a round the two possible addressing for a command Offset and Range data OffsetOrRange = ORO Offset | ORR Range | ORN deriving Show -- | a complete command is a Command coupled with a Range or an Offset data CompleteCommand = CC Command OffsetOrRange deriving Show -- | main datatype for the program-- beyond the core state, a simulation layer 'SIO' can be read -- and errors 'Err' can be thrown to kill the monad flow type Editor m w = ErrorT Err (StatoE m w) -- | wrap a maybe action and throw a backend error on a Nothing backend :: Ctx m w => Maybe a -- ^ maybe action -> Editor m w a -- ^ monading backend = maybe (throwError BackendErr) return -- | execute an action on the file through :: Ctx m w => (w -> Maybe a) -- ^ an action from an engine w to a maybe -> Editor m w a -- ^ the result from Just in the Editor monad through f = gets file >>= backend . f -- | the inputSio action lifted to Editor pinput :: Ctx m w => String -> Editor m w (Maybe String) pinput = liftSio . inputSio -- | the inputSio action lifted to Editor with empty prompt input :: Ctx m w => Editor m w (Maybe String) input = pinput "" -- | the outputSio action lifted to Editor output :: Ctx m w => String -> Editor m w () output = liftSio . outputSio -- | the historySIO action lifted to Editor history :: Ctx m w => String -> Editor m w () history = liftSio . historySio -- | the errorSIO action lifted to Editor errorlog :: Ctx m w => String -> Editor m w () errorlog = liftSio . errorSIO -- | editor runner . -- resolve the all monad from a core state to another run :: Ctx m w => Editor m w a -- ^ the action to run -> Stato w -- ^ the initial state -> m (Stato w) -- ^ the final state wrapped in the monad choosen for the SIO run editor w = flip execUndoT w $ runErrorT editor >>= \x -> case x of Left err -> lift $ errorSIO (show err) Right _ -> return ()