[docs paolo.veronelli@gmail.com**20080128204945] { addfile ./docs/Buffer.html hunk ./docs/Buffer.html 1 + + +Buffer
 ContentsIndex
Buffer
Description
An Editor backend implementation, made of the instance of Engine of InsideAppend. +
Synopsis
data InsideAppend
Documentation
data InsideAppend
See the Engine class docs +
show/hide Instances
Produced by Haddock version 0.8
addfile ./docs/Editor.html hunk ./docs/Editor.html 1 + + +Editor
 ContentsIndex
Editor
Description
Main datas and types for the editor +
Synopsis
data Stato w = Stato {
file :: w
lastre :: String
}
type StatoE m w = StateT (Stato w) m
class (Engine w, Monad m) => Ctx m w
data Err
= StopErr
| ParserErr String
| RegexUnmatched
| EvalErr String
| BackendErr
| Ahi String
data SIO m = SIO {
inputSio :: (String -> m (Maybe String))
outputSio :: (String -> m ())
historySio :: (String -> m ())
errorSIO :: (Err -> m ())
}
data Command
= Append
| Insert
| Change
| Delete
| Print
| SmallG String
| BigG String
| NoCommand
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 w = ErrorT Err (ReaderT (SIO m) (StatoE m w))
backend :: Ctx m w => Maybe a -> Editor m w a
through :: Ctx m w => (w -> Maybe a) -> Editor m w a
pinput :: Ctx m w => String -> Editor m w (Maybe String)
input :: Ctx m w => Editor m w (Maybe String)
output :: Ctx m w => String -> Editor m w ()
history :: Ctx m w => String -> Editor m w ()
errorlog :: Ctx m w => Err -> Editor m w ()
run :: Ctx m w => Editor m w a -> SIO m -> Stato w -> m (Stato w)
Documentation
data Stato w
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 :: wdata holding the file +
lastre :: Stringa regex +
show/hide Instances
Eq w => Eq (Stato w)
Show w => Show (Stato w)
type StatoE m w = StateT (Stato w) m
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 +
class (Engine w, Monad m) => Ctx m w
placeholder for the two constraints +
show/hide Instances
data Err
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 Stringsomething bad happened in the evaluation process (not implemented) +
BackendErrlines were addressed out of file (see Engine) +
Ahi Stringuncontrolled errors +
show/hide Instances
Error Err
Show Err
data SIO m
a layer for IO simulation, see programSIO for the real program one and testSio for tests +
Constructors
SIO
inputSio :: (String -> m (Maybe String))accepts a prompt and should return Nothing on eof else a line of input +
outputSio :: (String -> m ())output a normal string +
historySio :: (String -> m ())put a line in the history (which is global) +
errorSIO :: (Err -> m ())output an error string +
data Command
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 +
show/hide Instances
Show Command
data Offset
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
Show Offset
data Range
a couple of Offsets +
Constructors
Range Offset Offset
show/hide Instances
Show Range
data OffsetOrRange
wrapper a round the two possible addressing for a command Offset and Range +
Constructors
ORO Offset
ORR Range
ORN
show/hide Instances
data CompleteCommand
a complete command is a Command coupled with a Range or an Offset +
Constructors
CC Command OffsetOrRange
show/hide Instances
type Editor m w = ErrorT Err (ReaderT (SIO m) (StatoE m w))
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 +
backend
:: Ctx m w
=> Maybe amaybe action +
-> Editor m w amonading +
wrap a maybe action and throw a backend error on a Nothing +
through
:: Ctx m w
=> (w -> Maybe a)an action from an engine w to a maybe +
-> Editor m w athe result from Just in the Editor monad +
execute an action on the file +
pinput
:: Ctx m w
=> Stringthe prompt +
-> Editor m w (Maybe String)Nothing for eof or Just the line +
the inputSio action lifted to Editor +
input :: Ctx m w => Editor m w (Maybe String)
the inputSio action lifted to Editor with empty prompt +
output
:: Ctx m w
=> Stringwhat to output +
-> Editor m w ()monading .. +
the outputSio action lifted to Editor +
history
:: Ctx m w
=> Stringwhat to add to history stack +
-> Editor m w ()monading .. +
the historySIO action lifted to Editor +
errorlog
:: Ctx m w
=> Errthe error happened +
-> Editor m w ()monading +
the errorSIO action lifted to Editor +
run
:: Ctx m w
=> Editor m w athe action to run +
-> SIO mthe input output simulation to be used +
-> Stato wthe initial state +
-> m (Stato w)the 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 0.8
addfile ./docs/Engine.html hunk ./docs/Engine.html 1 + + +Engine
 ContentsIndex
Engine
Description
Abstraction on a zipped list. Use these instances to have a list cursored on a position, also + called double linked list. +
Synopsis
type Change a = a -> Maybe a
data Pos
= Line {
nth :: Int
}
| Begin
| End {
lns :: Int
}
class Eq a => Engine a where
empty :: a
listIn :: [String] -> a
listOut :: a -> Maybe [String]
linen :: Int -> a -> Maybe [String]
line :: a -> Maybe String
jump :: Int -> Change a
ins :: [String] -> Change a
add :: [String] -> Change a
del :: Change a
deln :: Int -> Change a
end :: Change a
start :: Change a
pos :: a -> Pos
next :: Change a
prev :: Change a
prevn :: Int -> Change a
nextn :: Int -> Change a
rjump :: Int -> Change a
tillend :: a -> Maybe [String]
fromstart :: a -> Maybe [String]
newtype W w = W w
prop_E1 :: Engine w => W w -> String -> Bool
Documentation
type Change a = a -> Maybe a
represent an action, which can fail with Nothing , an index error +
data Pos
Pos represent the position addressed in the engine +
Constructors
Linethe engine addresses a real line +
nth :: IntThe index of the line starting from 1 +
Beginthe engine addresses before first line , if ever present +
Endthe engine addresses after last line +
lns :: IntThe number of lines in the engine +
class Eq a => Engine a where
the class to implement for holding a list of elements with a cursor on them +
Methods
empty :: a
An empty engine +
listIn :: [String] -> a
An engine is isomorphic to a list +
listOut :: a -> Maybe [String]
Extract the list from the engine +
linen :: Int -> a -> Maybe [String]
Extract n lines from the position addressed +
line :: a -> Maybe String
Extract the addressed line +
jump :: Int -> Change a
Possibly set the addressed line to the nth line +
ins :: [String] -> Change a
Insert some lines before the addressed line +
add :: [String] -> Change a
Insert some lines after the addressed line +
del :: Change a
Delete the addressed line , address the next one +
deln :: Int -> Change a
Delete n lines from the addressed position +
end :: Change a
Address an append position +
start :: Change a
Address before the first line +
pos :: a -> Pos
The number of the addressed line +
next :: Change a
Address the next line +
prev :: Change a
Address the prev line +
prevn :: Int -> Change a
Jump back n lines +
nextn :: Int -> Change a
Jump ahead n lines +
rjump :: Int -> Change a
Jump n lines relative to the addredded line +
tillend :: a -> Maybe [String]
Get all the elements from the addressed one to the last one +
fromstart :: a -> Maybe [String]
Get all elemnts from the start to the addressed one included +
show/hide Instances
newtype W w
Constructors
W w
show/hide Instances
(Eq w, Engine w) => Arbitrary (W w)
Show w => Show (W w)
prop_E1 :: Engine w => W w -> String -> Bool
Produced by Haddock version 0.8
addfile ./docs/Eval.html hunk ./docs/Eval.html 1 + + +Eval
 ContentsIndex
Eval
Description
The logic of each of the available commands +
Synopsis
eval :: Ctx m w => CompleteCommand -> Editor m w ()
Documentation
eval
:: Ctx m w
=> CompleteCommandthe command to match for execution +
-> Editor m w ()monading .. +
every command is run with eval. See Command datatype for docs +
Produced by Haddock version 0.8
addfile ./docs/Main.html hunk ./docs/Main.html 1 + + +Main
 ContentsIndex
Main
Synopsis
data Console = Console {
cinput :: [Maybe String]
coutput :: [String]
}
type WESC = WriterT [Err] (State Console)
commandTest :: String -> [String] -> [String] -> [String] -> Either [Err] Bool
Documentation
data Console
Constructors
Console
cinput :: [Maybe String]
coutput :: [String]
type WESC = WriterT [Err] (State Console)
commandTest
:: StringThe command to test +
-> [String]What will be eventually read as input +
-> [String]The file as a list of line +
-> [String]The modified file +
-> Either [Err] BoolLeft on errors, Right with the test +
Testing a console function leaving out +
Produced by Haddock version 0.8
addfile ./docs/Offset.html hunk ./docs/Offset.html 1 + + +Offset
 ContentsIndex
Offset
Description
Operations involving Offset and Range through Engine interface +
Synopsis
jumpE :: Ctx m w => Offset -> Editor m w w
rangeResolve :: Ctx m w => Range -> Editor m w (Int, w)
doOffset :: Ctx m w => Offset -> (a -> Editor m w b) -> (w -> Maybe a) -> Editor m w b
editOffset :: Ctx m w => Offset -> (w -> Maybe w) -> Editor m w ()
doRange :: Ctx m w => Range -> (a -> Editor m w b) -> (Int -> w -> Maybe a) -> Editor m w b
editRange :: Ctx m w => Range -> (Int -> w -> Maybe w) -> Editor m w ()
Documentation
jumpE
:: Ctx m w
=> Offsetthe new position for the cursor +
-> Editor m w wthe modified engine under the Editor +
move the cursor in the engine +
rangeResolve
:: Ctx m w
=> Rangethe range to focus +
-> Editor m w (Int, w)the tuple (nelements,engine placed + at first offset of range) +
From a range to the tuple (nelements,starting range element) +
doOffset
:: Ctx m w
=> OffsetOffset for the action +
-> (a -> Editor m w b)the final action +
-> (w -> Maybe a)the backend ation +
-> Editor m w b.. +
a complete backend + Editor action on an Offset +
editOffset
:: Ctx m w
=> OffsetOffset for the backend action +
-> (w -> Maybe w)the backend ation +
-> Editor m w ()modified monad +
a backend action ending in a save state for the file +
doRange
:: Ctx m w
=> Rangethe addressed range +
-> (a -> Editor m w b)the closing Editor action +
-> (Int -> w -> Maybe a)the backend action +
-> Editor m w b... +
a complete backend + Editor action on a Range +
editRange
:: Ctx m w
=> Rangethe addressed range +
-> (Int -> w -> Maybe w)the backend action +
-> Editor m w ()modified monad +
Produced by Haddock version 0.8
addfile ./docs/Operation.html hunk ./docs/Operation.html 1 + + +Operation
 ContentsIndex
Operation
Description
Functions for read-eval-do managing +
Synopsis
commandMode :: Ctx m w => (String -> Either String CompleteCommand) -> (CompleteCommand -> Editor m w ()) -> Editor m w ()
commandLoop :: Ctx m w => (String -> Either String CompleteCommand) -> (CompleteCommand -> Editor m w ()) -> Editor m w ()
inputMode :: Ctx m w => Editor m w [String]
Documentation
commandMode
:: Ctx m w
=> (String -> Either String CompleteCommand)the parser for the command on the line +
-> (CompleteCommand -> Editor m w ())the evaluator for the parsed command +
-> Editor m w ()updated beast +
a step in main mode for the editor +
commandLoop
:: Ctx m w
=> (String -> Either String CompleteCommand)the parser for the command on the line +
-> (CompleteCommand -> Editor m w ())the evaluator for the parsed command +
-> Editor m w ()updated beast +
looping in main mode with error log on output +
inputMode :: Ctx m w => Editor m w [String]
the secondary mode for the editor where lines are inserted as input. It returns the lines.Use CTRL-D to exit +
Produced by Haddock version 0.8
addfile ./docs/Parser.html hunk ./docs/Parser.html 1 + + +Parser
 ContentsIndex
Parser
Synopsis
type ParseE = GenParser Char ()
numero :: ParseE Integer
parseOffset :: ParseE Offset
parseRange :: ParseE Range
defaultOR :: Command -> OffsetOrRange
acceptOffsetOnly :: Command -> OffsetOrRange -> ParseE ()
parseOffsetOrRange :: ParseE OffsetOrRange
rconst :: Command -> ParseE (OffsetOrRange -> ParseE Command)
parseCommand :: ParseE (OffsetOrRange -> ParseE Command)
parser :: ParseE CompleteCommand
parse :: String -> Either String CompleteCommand
Documentation
type ParseE = GenParser Char ()
shortcut for a parser of chars with no state +
numero :: ParseE Integer
parse an integer number +
parseOffset :: ParseE Offset
parse an Offset +
parseRange :: ParseE Range
parse a Range +
defaultOR :: Command -> OffsetOrRange
defaults Offset or Range for the commands +
acceptOffsetOnly :: Command -> OffsetOrRange -> ParseE ()
forces a failure for a command if a Range was parsed +
parseOffsetOrRange :: ParseE OffsetOrRange
parse an OffsetOrRange +
rconst :: Command -> ParseE (OffsetOrRange -> ParseE Command)
helper for skipping a filter +
parseCommand :: ParseE (OffsetOrRange -> ParseE Command)
parse a function from OffsetOrRange to a parse Command +
parser :: ParseE CompleteCommand
parse a CompleteCommand made of an OffsetOrRange and a Command +
parse :: String -> Either String CompleteCommand
the parser from a String to either a String representing an error or a CompleteCommand +
Produced by Haddock version 0.8
addfile ./docs/doc-index-A.html hunk ./docs/doc-index-A.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (A)
Absolute
Ahi
Append
acceptOffsetOnly
add
addfile ./docs/doc-index-B.html hunk ./docs/doc-index-B.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (B)
BackendErr
Begin
BigG
backend
addfile ./docs/doc-index-C.html hunk ./docs/doc-index-C.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (C)
CC
Change
1 (Data Constructor)
2 (Type/Class)
Command
CompleteCommand
Console
1 (Type/Class)
2 (Data Constructor)
Ctx
Current
cinput
commandLoop
commandMode
commandTest
coutput
addfile ./docs/doc-index-D.html hunk ./docs/doc-index-D.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (D)
Delete
defaultOR
del
deln
doOffset
doRange
addfile ./docs/doc-index-E.html hunk ./docs/doc-index-E.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (E)
Editor
End
Engine
Err
EvalErr
editOffset
editRange
empty
end
errorSIO
errorlog
eval
addfile ./docs/doc-index-F.html hunk ./docs/doc-index-F.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (F)
file
fromstart
addfile ./docs/doc-index-H.html hunk ./docs/doc-index-H.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (H)
history
historySio
addfile ./docs/doc-index-I.html hunk ./docs/doc-index-I.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (I)
Insert
InsideAppend
input
inputMode
inputSio
ins
addfile ./docs/doc-index-J.html hunk ./docs/doc-index-J.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (J)
jump
jumpE
addfile ./docs/doc-index-L.html hunk ./docs/doc-index-L.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (L)
LastLine
LastReNext
LastRePrev
Line
lastre
line
linen
listIn
listOut
lns
addfile ./docs/doc-index-M.html hunk ./docs/doc-index-M.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (M)
MarkedAs
addfile ./docs/doc-index-N.html hunk ./docs/doc-index-N.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (N)
Next
NoCommand
next
nextn
nth
numero
addfile ./docs/doc-index-O.html hunk ./docs/doc-index-O.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (O)
ORN
ORO
ORR
Offset
OffsetOrRange
output
outputSio
addfile ./docs/doc-index-P.html hunk ./docs/doc-index-P.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (P)
ParseE
ParserErr
Pos
Prev
Print
parse
parseCommand
parseOffset
parseOffsetOrRange
parseRange
parser
pinput
pos
prev
prevn
programSio
prop_E1
addfile ./docs/doc-index-R.html hunk ./docs/doc-index-R.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (R)
Range
1 (Type/Class)
2 (Data Constructor)
ReNext
RePrev
RegexUnmatched
rangeResolve
rconst
rjump
run
addfile ./docs/doc-index-S.html hunk ./docs/doc-index-S.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (S)
SIO
1 (Type/Class)
2 (Data Constructor)
SmallG
Stato
1 (Type/Class)
2 (Data Constructor)
StatoE
StopErr
start
addfile ./docs/doc-index-T.html hunk ./docs/doc-index-T.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (T)
through
tillend
addfile ./docs/doc-index-W.html hunk ./docs/doc-index-W.html 1 + + + (Index)
 ContentsIndex
ABCDEFHIJLMNOPRSTW
Index (W)
W
1 (Type/Class)
2 (Data Constructor)
WESC
addfile ./docs/doc-index.html hunk ./docs/doc-index.html 1 + + + (Index)
 ContentsIndex
Index
ABCDEFHIJLMNOPRSTW
addfile ./docs/haddock.css hunk ./docs/haddock.css 1 +/* -------- Global things --------- */ + +BODY { + background-color: #ffffff; + color: #000000; + font-family: sans-serif; + } + +A:link { color: #0000e0; text-decoration: none } +A:visited { color: #0000a0; text-decoration: none } +A:hover { background-color: #e0e0ff; text-decoration: none } + +TABLE.vanilla { + width: 100%; + border-width: 0px; + /* I can't seem to specify cellspacing or cellpadding properly using CSS... */ +} + +TABLE.vanilla2 { + border-width: 0px; +} + +/* font is a little too small in MSIE */ +TT { font-size: 100%; } +PRE { font-size: 100%; } + +LI P { margin: 0pt } + +TD { + border-width: 0px; +} + +TABLE.narrow { + border-width: 0px; +} + +TD.s8 { height: 8px; } +TD.s15 { height: 15px; } + +SPAN.keyword { text-decoration: underline; } + +/* Resize the buttom image to match the text size */ +IMG.coll { width : 0.75em; height: 0.75em; margin-bottom: 0; margin-right: 0.5em } + +/* --------- Contents page ---------- */ + +DIV.node { + padding-left: 3em; +} + +DIV.cnode { + padding-left: 1.75em; +} + +SPAN.pkg { + position: absolute; + left: 50em; +} + +/* --------- Documentation elements ---------- */ + +TD.children { + padding-left: 25px; + } + +TD.synopsis { + padding: 2px; + background-color: #f0f0f0; + font-family: monospace + } + +TD.decl { + padding: 2px; + background-color: #f0f0f0; + font-family: monospace; + vertical-align: top; + } + +TD.topdecl { + padding: 2px; + background-color: #f0f0f0; + font-family: monospace; + vertical-align: top; +} + +TABLE.declbar { + border-spacing: 0px; + } + +TD.declname { + width: 100%; + } + +TD.declbut { + padding-left: 5px; + padding-right: 5px; + border-left-width: 1px; + border-left-color: #000099; + border-left-style: solid; + white-space: nowrap; + font-size: small; + } + +/* + arg is just like decl, except that wrapping is not allowed. It is + used for function and constructor arguments which have a text box + to the right, where if wrapping is allowed the text box squashes up + the declaration by wrapping it. +*/ +TD.arg { + padding: 2px; + background-color: #f0f0f0; + font-family: monospace; + vertical-align: top; + white-space: nowrap; + } + +TD.recfield { padding-left: 20px } + +TD.doc { + padding-top: 2px; + padding-left: 10px; + } + +TD.ndoc { + padding: 2px; + } + +TD.rdoc { + padding: 2px; + padding-left: 10px; + width: 100%; + } + +TD.body { + padding-left: 10px + } + +TD.pkg { + width: 100%; + padding-left: 10px +} + +TD.indexentry { + vertical-align: top; + padding-right: 10px + } + +TD.indexannot { + vertical-align: top; + padding-left: 20px; + white-space: nowrap + } + +TD.indexlinks { + width: 100% + } + +/* ------- Section Headings ------- */ + +TD.section1 { + padding-top: 15px; + font-weight: bold; + font-size: 150% + } + +TD.section2 { + padding-top: 10px; + font-weight: bold; + font-size: 130% + } + +TD.section3 { + padding-top: 5px; + font-weight: bold; + font-size: 110% + } + +TD.section4 { + font-weight: bold; + font-size: 100% + } + +/* -------------- The title bar at the top of the page */ + +TD.infohead { + color: #ffffff; + font-weight: bold; + padding-right: 10px; + text-align: left; +} + +TD.infoval { + color: #ffffff; + padding-right: 10px; + text-align: left; +} + +TD.topbar { + background-color: #000099; + padding: 5px; +} + +TD.title { + color: #ffffff; + padding-left: 10px; + width: 100% + } + +TD.topbut { + padding-left: 5px; + padding-right: 5px; + border-left-width: 1px; + border-left-color: #ffffff; + border-left-style: solid; + white-space: nowrap; + } + +TD.topbut A:link { + color: #ffffff + } + +TD.topbut A:visited { + color: #ffff00 + } + +TD.topbut A:hover { + background-color: #6060ff; + } + +TD.topbut:hover { + background-color: #6060ff + } + +TD.modulebar { + background-color: #0077dd; + padding: 5px; + border-top-width: 1px; + border-top-color: #ffffff; + border-top-style: solid; + } + +/* --------- The page footer --------- */ + +TD.botbar { + background-color: #000099; + color: #ffffff; + padding: 5px + } +TD.botbar A:link { + color: #ffffff; + text-decoration: underline + } +TD.botbar A:visited { + color: #ffff00 + } +TD.botbar A:hover { + background-color: #6060ff + } + addfile ./docs/haddock.js hunk ./docs/haddock.js 1 +// Haddock JavaScript utilities +function toggle(button,id) +{ + var n = document.getElementById(id).style; + if (n.display == "none") + { + button.src = "minus.gif"; + n.display = "block"; + } + else + { + button.src = "plus.gif"; + n.display = "none"; + } +} addfile ./docs/haskell_icon.gif binary ./docs/haskell_icon.gif oldhex * newhex *47494638376110001000f70f00000000800000008000808000000080800080008080c0c0c08080 *80ff000000ff00ffff000000ffff00ff00ffffffffff0000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *000000000000000000000000000000000000000000000000000000000000000000000000000000 *0021f90401000000002c000000001000100007086c0001007840b0a0418202073e38b0b021c387 *07143e2440c0a143040e091cd0787021c686151f84347800e343901d4b12646870e44a930d0952 *3ca832a6cc990555b2bc2992e4c79d3847ea2c88b3a7c89a2c8b8aa43874e941a60810003840b5 *aa55aa511346ddca75abc080003b addfile ./docs/index.html hunk ./docs/index.html 1 + + +
 ContentsIndex
Modules
Buffer
Editor
Engine
Eval
Main
Offset
Operation
Parser
Produced by Haddock version 0.8
addfile ./docs/minus.gif binary ./docs/minus.gif oldhex * newhex *47494638396109000900910000fefefe8282820202020000002c00000000090009000002118c8f *a00bc6eb5e0b40583b6596f1a11f14003b addfile ./docs/plus.gif binary ./docs/plus.gif oldhex * newhex *47494638396109000900910000fefefe8282820202020000002c00000000090009000002148c8f *a00bb6b29c82ca897b5b7871cfce74085200003b }