Hedi-0.1.1: Line oriented editorSource codeContentsIndex
Editor
Description
Main datas and types for the editor
Synopsis
data Stato = Stato {
file :: Engine
lastre :: String
filename :: Maybe String
pending :: Maybe Command
lastsaved :: Maybe Engine
}
type StatoE m = UndoT Stato m
liftStatoE :: Ctx m => StatoE m a -> Editor m a
hputfile :: Ctx m => Engine -> Editor m ()
class (SIO m, HCtx m Stato) => Ctx m
data Err
= StopErr
| ParserErr String
| RegexUnmatched
| EvalErr Err
| BackendErr
| Ahi String
| FileReadErr String
| FileNameMissing
| FileWriteErr String
| ExternalCommandErr String
| PendingState Command
| NoMoreUndo
| NoMoreRedo
| CommandHelpMissing
| CommandHelpParseErr String
class Monad m => SIO m where
inputSio :: String -> m (Maybe String)
outputSio :: String -> m ()
historySio :: String -> m ()
errorSIO :: String -> m ()
readfileSio :: String -> ErrorT String m String
writefileSio :: String -> String -> ErrorT String m ()
externalSio :: String -> ErrorT String m String
commandhelpSIO :: m FilePath
liftSio :: Ctx m => m a -> Editor m a
data Command
= Append
| Insert
| Change
| Delete
| Print
| SmallG String
| BigG String
| NoCommand
| Edit String
| Write
| WriteNew String
| SetFilename String
| GetFilename
| EditExternal String
| UndoChange
| RedoChange
| HelpList
| HelpTopic String
data Offset
= LastLine
| Absolute Int
| Current
| Prev Int
| Next Int
| ReNext String
| LastReNext
| RePrev String
| LastRePrev
| MarkedAs Char
data Range = Range Offset Offset
data OffsetOrRange
= ORO Offset
| ORR Range
| ORN
data CompleteCommand = CC Command OffsetOrRange
type Editor m = ErrorT Err (StatoE m)
backend :: Ctx m => Maybe a -> Editor m a
through :: Ctx m => (Engine -> Maybe a) -> Editor m a
pinput :: Ctx m => String -> Editor m (Maybe String)
input :: Ctx m => Editor m (Maybe String)
output :: Ctx m => String -> Editor m ()
history :: Ctx m => String -> Editor m ()
errorlog :: Ctx m => String -> Editor m ()
run :: Ctx m => Editor m a -> Stato -> m Stato
Documentation
data Stato Source
Stato is parametrized on an Engine instance and hold the engine with the last regex entered , regex G and g are not implemented now
Constructors
Stato
file :: Enginedata holding the file
lastre :: Stringa regex
filename :: Maybe Stringthe file we are editing
pending :: Maybe Commanda sensible state for data lost
lastsaved :: Maybe Engine
show/hide Instances
type StatoE m = UndoT Stato mSource
the core editor runs under the state monad with state (Stato) . Wrapped around a monad (IO mainly) to permit console input and output of commands with IO and testing with State
liftStatoE :: Ctx m => StatoE m a -> Editor m aSource
hputfile :: Ctx m => Engine -> Editor m ()Source
push a new file (data Engine instance) in the core State, pushing the old state in the undo stack
class (SIO m, HCtx m Stato) => Ctx m Source
placeholder for the two constraints
data Err Source
the errors (monad failers) which can break the monad flow
Constructors
StopErrissued on ctrl-d or q command (q not implemented)
ParserErr Stringcommand line was not parsed to a CompleteCommand
RegexUnmatchedthe regex doesn't match a line
EvalErr Errsomething bad happened in the evaluation process
BackendErrlines were addressed out of file (see Engine)
Ahi Stringuncontrolled errors
FileReadErr Stringio error trying to load a file
FileNameMissingfilename is not set
FileWriteErr Stringio error trying to write the file
ExternalCommandErr Stringio error executing an external program
PendingState Commanda sensible data discarding command has been entered
NoMoreUndoreached the first state remembered
NoMoreRedoreached the last state remembered
CommandHelpMissinga help for a missing command was asked
CommandHelpParseErr Stringerror parsing the help for commands
show/hide Instances
class Monad m => SIO m whereSource
a layer for IO simulation, see Main for the real program one and Test for tests
Methods
inputSio :: String -> m (Maybe String)Source
accepts a prompt and should return Nothing on eof else a line of input
outputSioSource
:: String
-> m ()output a normal string
historySioSource
:: String
-> m ()put a line in the history (which is global)
errorSIOSource
:: String
-> m ()output an error string
readfileSioSource
:: String
-> ErrorT String m Stringread a file
writefileSioSource
:: 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 StringSource
commandhelpSIO :: m FilePathSource
show/hide Instances
liftSio :: Ctx m => m a -> Editor m aSource
data Command Source
commands for the editor
Constructors
Appendget some text and add it after the addressed line
Insertget some text and add it before the addressed line
Changeget some text and add it in place of some deleted lines
Deletedelete some lines
Printprint some lines
SmallG Stringget some commands and execute them on each line matching a regex
BigG Stringinteractively execute commands on each line matching a regex
NoCommandChange the addressed line
Edit StringLoad a file
WriteWrite the file
WriteNew StringWrite a new file
SetFilename StringSet filename
GetFilenamePrint filename
EditExternal StringLoad the output of an external command
UndoChangeRevert the last change if ever
RedoChangeRestore via the last change
HelpListAsking help
HelpTopic StringSpedific help
show/hide Instances
data Offset Source
represents a line position in the file
Constructors
LastLinebeyond last line, the append line
Absolute Intthe nth line
Currentthe line addressed by the engine
Prev Intthe nth line before the addressed one
Next Intthe nth line aftor the addressed one
ReNext Stringthe next line (wrapping around) matching a regex
LastReNextthe next line matching the last learned regex
RePrev Stringthe previous line (wrapping around) matching a regex
LastRePrevthe previous matching the last learned regex
MarkedAs Charthe line marked previously with a char
show/hide Instances
data Range Source
a couple of Offsets
Constructors
Range Offset Offset
show/hide Instances
data OffsetOrRange Source
wrapper a round the two possible addressing for a command Offset and Range
Constructors
ORO Offset
ORR Range
ORN
show/hide Instances
data CompleteCommand Source
a complete command is a Command coupled with a Range or an Offset
Constructors
CC Command OffsetOrRange
show/hide Instances
type Editor m = ErrorT Err (StatoE m)Source
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
backendSource
:: Ctx m
=> Maybe amaybe action
-> Editor m amonading
wrap a maybe action and throw a backend error on a Nothing
throughSource
:: Ctx m
=> Engine -> Maybe aan action from an engine w to a maybe
-> Editor m athe result from Just in the Editor monad
execute an action on the file
pinput :: Ctx m => String -> Editor m (Maybe String)Source
the inputSio action lifted to Editor
input :: Ctx m => Editor m (Maybe String)Source
the inputSio action lifted to Editor with empty prompt
output :: Ctx m => String -> Editor m ()Source
the outputSio action lifted to Editor
history :: Ctx m => String -> Editor m ()Source
the historySIO action lifted to Editor
errorlog :: Ctx m => String -> Editor m ()Source
the errorSIO action lifted to Editor
runSource
:: Ctx m
=> Editor m athe action to run
-> Statothe initial state
-> m Statothe final state wrapped in the monad choosen for the SIO
editor runner . resolve the all monad from a core state to another
Produced by Haddock version 2.3.0