site: fix man page TOCs, add combined man page
This commit is contained in:
		
							parent
							
								
									bba7909165
								
							
						
					
					
						commit
						443b870481
					
				
							
								
								
									
										67
									
								
								Shake.hs
									
									
									
									
									
								
							
							
						
						
									
										67
									
								
								Shake.hs
									
									
									
									
									
								
							| @ -19,9 +19,10 @@ Requires: https://www.haskell.org/downloads#stack | ||||
| 
 | ||||
| Shake notes: | ||||
|  wishlist: | ||||
|   just one shake import | ||||
|   wildcards in phony rules | ||||
|   multiple individually accessible wildcards | ||||
|   just one shake import | ||||
|   not having to write :: Action ExitCode after a non-final cmd | ||||
| -} | ||||
| 
 | ||||
| {-# LANGUAGE PackageImports, QuasiQuotes #-} | ||||
| @ -41,9 +42,10 @@ usage = [i|Usage: | ||||
|  ./Shake.hs compile       # compile this script (optional) | ||||
|  ./Shake --help           # show options, eg --color | ||||
|  ./Shake                  # show commands | ||||
|  ./Shake docs             # generate all docs | ||||
|  ./Shake site             # generate things needed for the website | ||||
|  ./Shake manpages         # generate nroff files for man | ||||
|  ./Shake webmanpages      # generate web man pages for hakyll | ||||
|  ./Shake webmanual        # generate combined web man page for hakyll | ||||
|  ./Shake m4manpages       # generate nroff files for man (alternate method) | ||||
|  ./Shake m4webmanpages    # generate web man pages for hakyll (alternate method) | ||||
| |] | ||||
| @ -52,15 +54,15 @@ buildDir = ".build" | ||||
| pandoc = | ||||
|   -- "stack exec -- pandoc" -- use the pandoc required above | ||||
|   "pandoc"                  -- use pandoc in PATH (faster) | ||||
| manpages = [ | ||||
|    "hledger_csv.5" | ||||
|   ,"hledger_journal.5" | ||||
|   ,"hledger_timedot.5" | ||||
|   ,"hledger_timelog.5" | ||||
|   ,"hledger.1" | ||||
|   ,"hledger-api.1" | ||||
| manpages = [ -- in suggested reading order | ||||
|    "hledger.1" | ||||
|   ,"hledger-ui.1" | ||||
|   ,"hledger-web.1" | ||||
|   ,"hledger-api.1" | ||||
|   ,"hledger_journal.5" | ||||
|   ,"hledger_csv.5" | ||||
|   ,"hledger_timelog.5" | ||||
|   ,"hledger_timedot.5" | ||||
|   ] | ||||
| 
 | ||||
| manpageDir p | ||||
| @ -92,13 +94,17 @@ main = do | ||||
| 
 | ||||
|     -- docs | ||||
| 
 | ||||
|     -- method 1: | ||||
| 
 | ||||
|     phony "docs" $ need [ | ||||
|     phony "site" $ need [ | ||||
|        "manpages" | ||||
|       ,"webmanpages" | ||||
|       ,"m4manpages" | ||||
|       ,"m4webmanpages" | ||||
|       ,"site/manual2.md" | ||||
|       ] | ||||
| 
 | ||||
|     -- man pages | ||||
|     -- method 1: | ||||
| 
 | ||||
|     -- pandoc filters, these adjust master md files for web or man output | ||||
|     phony "pandocfilters" $ need pandocFilters | ||||
|     pandocFilters |%> \out -> do | ||||
| @ -127,15 +133,13 @@ main = do | ||||
|       let p = dropExtension $ takeFileName out | ||||
|           md = manpageDir p </> p <.> "md" | ||||
|       need $ md : pandocFilters | ||||
|       cmd pandoc md "-o" out "--filter doc/pandoc-drop-man-blocks" | ||||
|       cmd pandoc md "-o" out | ||||
|         "--filter doc/pandoc-demote-headers" | ||||
|         -- "--filter doc/pandoc-add-toc" | ||||
|         -- "--filter doc/pandoc-drop-man-blocks" | ||||
| 
 | ||||
|     -- method 2: | ||||
| 
 | ||||
|     phony "m4docs" $ need [ | ||||
|        "m4manpages" | ||||
|       ,"m4webmanpages" | ||||
|       ] | ||||
| 
 | ||||
|     -- man pages assembled from parts and adjusted for man with m4, adjusted more and converted to nroff with pandoc | ||||
|     let m4manpageNroffs = [manpageDir p </> "m4-"++p | p <- ["hledger.1"]] | ||||
|     phony "m4manpages" $ need m4manpageNroffs | ||||
| @ -146,7 +150,8 @@ main = do | ||||
|           m4lib = "doc/lib.m4" | ||||
|           tmpl  = "doc/manpage.nroff" | ||||
|       need $ m4src : m4lib : tmpl : pandocFilters ++ m4includes | ||||
|       cmd Shell "m4 -P" "-DMAN" "-I" dir m4lib m4src "|" pandoc "-s --template" tmpl "-o" out | ||||
|       cmd Shell "m4 -P" "-DMAN" "-I" dir m4lib m4src | ||||
|         "|" pandoc "-s --template" tmpl "-o" out | ||||
|         "--filter doc/pandoc-drop-html-blocks" | ||||
|         "--filter doc/pandoc-drop-html-inlines" | ||||
|         "--filter doc/pandoc-drop-links" | ||||
| @ -164,17 +169,35 @@ main = do | ||||
|           m4includes = map (dir </>) ["description.md","examples.md","queries.md","commands.md","options.md"] | ||||
|           m4lib = "doc/lib.m4" | ||||
|       need $ m4src : m4lib : m4includes | ||||
|       cmd Shell "m4 -P" "-DWEB" "-I" dir m4lib m4src "|" pandoc "-o" out | ||||
|       cmd Shell "m4 -P" "-DMAN -DWEB" "-I" dir m4lib m4src | ||||
|         "|" pandoc "-o" out | ||||
|         "--filter doc/pandoc-demote-headers" | ||||
|         -- "--filter doc/pandoc-add-toc" | ||||
| 
 | ||||
|     -- web manual combined from man pages | ||||
| 
 | ||||
|     let webmanual = "site/manual2.md" | ||||
|     phony "webmanual" $ need [ webmanual ] | ||||
|     "site/manual2.md" %> \out -> do | ||||
|       need webManpageMds | ||||
|       cmd Shell "printf '* toc\\n\\n' >" webmanual :: Action ExitCode | ||||
|       forM_ webManpageMds $ \f -> do | ||||
|         let manpage = dropExtension $ takeFileName f | ||||
|         cmd Shell ("printf '\\n## "++ manpage ++"\\n\\n' >>") webmanual :: Action ExitCode | ||||
|         cmd Shell "pandoc" f "-t markdown" | ||||
|           "--filter doc/pandoc-drop-toc" | ||||
|           "--filter doc/pandoc-demote-headers" | ||||
|           ">>" webmanual :: Action ExitCode | ||||
| 
 | ||||
|     -- cleanup | ||||
| 
 | ||||
|     phony "clean" $ do | ||||
|       putNormal "Cleaning generated files" | ||||
|       -- removeFilesAfter "." manpageNroffs | ||||
|       removeFilesAfter "." webManpageMds | ||||
|       removeFilesAfter "." m4manpageNroffs | ||||
|       removeFilesAfter "." $ map (<.> "md") m4manpageNroffs | ||||
|       removeFilesAfter "." webManpageMds | ||||
|       removeFilesAfter "." m4webManpageMds | ||||
|       removeFilesAfter "." [webmanual] | ||||
| 
 | ||||
|     phony "Clean" $ do | ||||
|       need ["clean"] | ||||
|  | ||||
							
								
								
									
										2
									
								
								doc/.gitignore
									
									
									
									
										vendored
									
									
								
							
							
						
						
									
										2
									
								
								doc/.gitignore
									
									
									
									
										vendored
									
									
								
							| @ -1,7 +1,9 @@ | ||||
| pandoc-add-toc | ||||
| pandoc-capitalize-headers | ||||
| pandoc-drop-html-blocks | ||||
| pandoc-drop-html-inlines | ||||
| pandoc-drop-links | ||||
| pandoc-drop-man-blocks | ||||
| pandoc-drop-notes | ||||
| pandoc-drop-toc | ||||
| pandoc-drop-web-blocks | ||||
|  | ||||
							
								
								
									
										121
									
								
								doc/pandoc-add-toc.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										121
									
								
								doc/pandoc-add-toc.hs
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,121 @@ | ||||
| #!/usr/bin/env stack | ||||
| {- stack runghc --verbosity info | ||||
|    --package pandoc | ||||
| -} | ||||
| -- Replace a table of contents marker | ||||
| -- (a bullet list item containing "toc[-N[-M]]") | ||||
| -- with a table of contents based on headings. | ||||
| -- toc means full contents, toc-N means contents to depth N | ||||
| -- and toc-N-M means contents from depth N to depth M. | ||||
| -- Based on code from https://github.com/blaenk/blaenk.github.io | ||||
| 
 | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| 
 | ||||
| import Data.Char (isDigit) | ||||
| import Data.List (groupBy) | ||||
| import Data.List.Split | ||||
| import Data.Tree (Forest, Tree(Node)) | ||||
| import Data.Monoid ((<>), mconcat) | ||||
| import Data.Function (on) | ||||
| import Data.Maybe (fromMaybe) | ||||
| import Safe | ||||
| import Text.Blaze.Html (preEscapedToHtml, (!)) | ||||
| import Text.Blaze.Html.Renderer.String (renderHtml) | ||||
| import qualified Text.Blaze.Html5 as H | ||||
| import qualified Text.Blaze.Html5.Attributes as A | ||||
| import Text.Pandoc | ||||
| import Text.Pandoc.JSON | ||||
| import Text.Pandoc.Walk (walk, query) | ||||
| 
 | ||||
| main :: IO () | ||||
| main = toJSONFilter tableOfContents | ||||
| 
 | ||||
| tableOfContents :: Pandoc -> Pandoc | ||||
| tableOfContents doc = | ||||
|   let headers = query collectHeaders doc | ||||
|   in walk (generateTOC headers) doc | ||||
| 
 | ||||
| collectHeaders :: Block -> [Block] | ||||
| collectHeaders header@(Header _ (_, classes, _) _) | ||||
|   | "notoc" `elem` classes = [] | ||||
|   | otherwise              = [header] | ||||
| collectHeaders _ = [] | ||||
| 
 | ||||
| generateTOC :: [Block] -> Block -> Block | ||||
| generateTOC [] x = x | ||||
| generateTOC headers x@(BulletList (( (( Plain ((Str txt):_)):_)):_)) = | ||||
|   case tocParams txt of | ||||
|   Just (mstartlevel, mendlevel) ->  | ||||
|     render . | ||||
|     forestDrop mstartlevel . | ||||
|     forestPrune mendlevel . | ||||
|     groupByHierarchy $ | ||||
|     headers -- (! A.class_ "right-toc") . | ||||
|     where | ||||
|       render = (RawBlock "html") . renderHtml . createTable | ||||
|   Nothing -> x | ||||
| generateTOC _ x = x | ||||
| 
 | ||||
| tocParams :: String -> Maybe (Maybe Int, Maybe Int) | ||||
| tocParams s = | ||||
|   case splitOn "-" s of | ||||
|   ["toc"]                                    -> Just (Nothing, Nothing) | ||||
|   ["toc",a]   | all isDigit a                -> Just (Nothing, readMay a) | ||||
|   ["toc",a,b] | all isDigit a, all isDigit b -> Just (readMay a, readMay b) | ||||
|   _                                          -> Nothing | ||||
| 
 | ||||
| forestDrop :: Maybe Int -> Forest a -> Forest a | ||||
| forestDrop Nothing f = f | ||||
| forestDrop (Just n) ts = concatMap (treeDrop n) ts | ||||
| 
 | ||||
| treeDrop :: Int -> Tree a -> Forest a | ||||
| treeDrop n t | n < 1 = [t] | ||||
| treeDrop n (Node _ ts) = concatMap (treeDrop (n-1)) ts | ||||
| 
 | ||||
| forestPrune :: Maybe Int -> Forest a -> Forest a | ||||
| forestPrune Nothing f = f | ||||
| forestPrune (Just n) ts = map (treePrune n) ts | ||||
| 
 | ||||
| treePrune :: Int -> Tree a -> Tree a | ||||
| treePrune n t | n < 1 = t | ||||
| treePrune n (Node v ts) = Node v $ map (treePrune (n-1)) ts | ||||
| 
 | ||||
| -- | remove all nodes past a certain depth | ||||
| -- treeprune :: Int -> Tree a -> Tree a | ||||
| -- treeprune 0 t = Node (root t) [] | ||||
| -- treeprune d t = Node (root t) (map (treeprune $ d-1) $ branches t) | ||||
| 
 | ||||
| groupByHierarchy :: [Block] -> Forest Block | ||||
| groupByHierarchy = map (\(x:xs) -> Node x (groupByHierarchy xs)) . groupBy ((<) `on` headerLevel) | ||||
| 
 | ||||
| headerLevel :: Block -> Int | ||||
| headerLevel (Header level _ _) = level | ||||
| headerLevel _ = error "not a header" | ||||
| 
 | ||||
| createTable :: Forest Block -> H.Html | ||||
| createTable headers = | ||||
|   (H.nav ! A.id "toc") $ do | ||||
|     H.p "Contents" | ||||
|     H.ol $ markupHeaders headers | ||||
| 
 | ||||
| markupHeader :: Tree Block -> H.Html | ||||
| markupHeader (Node (Header _ (ident, _, keyvals) inline) headers) | ||||
|   | headers == [] = H.li $ link | ||||
|   | otherwise     = H.li $ link <> (H.ol $ markupHeaders headers) | ||||
|   where render x  = writeHtmlString def (Pandoc nullMeta [(Plain x)]) | ||||
|         section   = fromMaybe (render inline) (lookup "toc" keyvals) | ||||
|         link      = H.a ! A.href (H.toValue $ "#" ++ ident) $ preEscapedToHtml section | ||||
| markupHeader _ = error "what" | ||||
| 
 | ||||
| markupHeaders :: Forest Block -> H.Html | ||||
| markupHeaders = mconcat . map markupHeader | ||||
| 
 | ||||
| -- ignoreTOC :: Block -> Block | ||||
| -- ignoreTOC (Header level (ident, classes, params) inline) = | ||||
| --   Header level (ident, "notoc" : classes, params) inline | ||||
| -- ignoreTOC x = x | ||||
| 
 | ||||
| -- removeTOCMarker :: Block -> Block | ||||
| -- removeTOCMarker (BulletList (( (( Plain ((Str "toc"):_)):_)):_)) = Null | ||||
| -- removeTOCMarker x = x | ||||
| 
 | ||||
							
								
								
									
										40
									
								
								doc/pandoc-drop-toc.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										40
									
								
								doc/pandoc-drop-toc.hs
									
									
									
									
									
										Normal file
									
								
							| @ -0,0 +1,40 @@ | ||||
| #!/usr/bin/env stack | ||||
| {- stack runghc --verbosity info | ||||
|    --package pandoc | ||||
| -} | ||||
| -- Remove a table of contents marker | ||||
| -- (a bullet list item containing "toc[-N[-M]]") | ||||
| 
 | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| 
 | ||||
| import Data.Char (isDigit) | ||||
| import Data.List.Split | ||||
| import Data.Maybe | ||||
| import Safe | ||||
| import Text.Pandoc.JSON | ||||
| 
 | ||||
| main :: IO () | ||||
| main = toJSONFilter dropToc | ||||
| 
 | ||||
| dropHtmlBlocks :: Block -> Block | ||||
| dropHtmlBlocks (RawBlock (Format "html") _) = Plain [] | ||||
| dropHtmlBlocks x = x | ||||
| 
 | ||||
|  -- BulletList | ||||
|  --  [ [Plain [Str "toc"]] ] | ||||
| dropToc :: Block -> Block | ||||
| dropToc (BulletList is) = | ||||
|   BulletList $ filter (not.null) $ map (filter isNotToc) is | ||||
|   where | ||||
|     isNotToc (Plain [Str s]) | isJust $ tocParams s = False | ||||
|     isNotToc _ = True | ||||
| dropToc x = x | ||||
| 
 | ||||
| tocParams :: String -> Maybe (Maybe Int, Maybe Int) | ||||
| tocParams s = | ||||
|   case splitOn "-" s of | ||||
|   ["toc"]                                    -> Just (Nothing, Nothing) | ||||
|   ["toc",a]   | all isDigit a                -> Just (Nothing, readMay a) | ||||
|   ["toc",a,b] | all isDigit a, all isDigit b -> Just (readMay a, readMay b) | ||||
|   _                                          -> Nothing | ||||
| 
 | ||||
| @ -2,6 +2,9 @@ | ||||
| % | ||||
| % January 2016 | ||||
| 
 | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| @ -19,9 +22,6 @@ hledger is a cross-platform program for tracking money, time, or any other commo | ||||
| using double-entry accounting and a simple, editable file format. | ||||
| hledger is inspired by and largely compatible with ledger(1). | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| <!-- * toc --> | ||||
| </div> | ||||
| 
 | ||||
| hledger-api is a simple web API server, intended to support | ||||
|  | ||||
| @ -2,6 +2,9 @@ | ||||
| % | ||||
| % October 2015 | ||||
| 
 | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| @ -10,9 +13,6 @@ hledger_csv - reading CSV files with hledger, and the CSV rules file format | ||||
| 
 | ||||
| # DESCRIPTION | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| 
 | ||||
| hledger can read | ||||
|  | ||||
| @ -2,6 +2,9 @@ | ||||
| % | ||||
| % October 2015 | ||||
| 
 | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| @ -10,9 +13,6 @@ hledger_journal - reference for hledger's journal file format | ||||
| 
 | ||||
| # DESCRIPTION | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| 
 | ||||
| hledger's usual data source is a plain text file containing journal entries in hledger journal format. | ||||
|  | ||||
| @ -2,6 +2,9 @@ | ||||
| % | ||||
| % February 2016 | ||||
| 
 | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| @ -10,9 +13,6 @@ hledger_timedot - time logging format | ||||
| 
 | ||||
| # DESCRIPTION | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| 
 | ||||
| Timedot is a plain text format for logging dated, categorised quantities (eg time), supported by hledger. | ||||
|  | ||||
| @ -2,6 +2,9 @@ | ||||
| %  | ||||
| % October 2015 | ||||
| 
 | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| @ -10,9 +13,6 @@ hledger_timelog - hledger's timelog file format | ||||
| 
 | ||||
| # DESCRIPTION | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| <!-- * toc --> | ||||
| </div> | ||||
| 
 | ||||
| hledger can read timelog files. | ||||
|  | ||||
| @ -2,24 +2,6 @@ | ||||
| % | ||||
| % October 2015 | ||||
| 
 | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| 
 | ||||
| hledger-ui - curses-style interface for the hledger accounting tool | ||||
| 
 | ||||
| # SYNOPSIS | ||||
| 
 | ||||
| `hledger-ui [OPTIONS] [QUERYARGS]`\ | ||||
| `hledger ui -- [OPTIONS] [QUERYARGS]` | ||||
| 
 | ||||
| # DESCRIPTION | ||||
| 
 | ||||
| hledger is a cross-platform program for tracking money, time, or any other commodity, | ||||
| using double-entry accounting and a simple, editable file format. | ||||
| hledger is inspired by and largely compatible with ledger(1). | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| * toc | ||||
| 
 | ||||
| @ -36,6 +18,23 @@ hledger is inspired by and largely compatible with ledger(1). | ||||
| <a href="images/hledger-ui/hledger-ui-bcexample-acc.png" class="highslide" onclick="return hs.expand(this)"><img src="images/hledger-ui/hledger-ui-bcexample-acc.png" title="beancount example accounts" /></a> | ||||
| <a href="images/hledger-ui/hledger-ui-bcexample-acc-etrade:cash.png" class="highslide" onclick="return hs.expand(this)"><img src="images/hledger-ui/hledger-ui-bcexample-acc-etrade:cash.png" title="beancount example's etrade cash subaccount" /></a> | ||||
| <a href="images/hledger-ui/hledger-ui-bcexample-acc-etrade.png" class="highslide" onclick="return hs.expand(this)"><img src="images/hledger-ui/hledger-ui-bcexample-acc-etrade.png" title="beancount example's etrade investments, all commoditiess" /></a> | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| 
 | ||||
| hledger-ui - curses-style interface for the hledger accounting tool | ||||
| 
 | ||||
| # SYNOPSIS | ||||
| 
 | ||||
| `hledger-ui [OPTIONS] [QUERYARGS]`\ | ||||
| `hledger ui -- [OPTIONS] [QUERYARGS]` | ||||
| 
 | ||||
| # DESCRIPTION | ||||
| 
 | ||||
| hledger is a cross-platform program for tracking money, time, or any other commodity, | ||||
| using double-entry accounting and a simple, editable file format. | ||||
| hledger is inspired by and largely compatible with ledger(1). | ||||
| 
 | ||||
| </div> | ||||
| 
 | ||||
|  | ||||
| @ -2,8 +2,10 @@ | ||||
| % | ||||
| % October 2015 | ||||
| 
 | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| 
 | ||||
| hledger-web - web interface for the hledger accounting tool | ||||
| @ -18,10 +20,6 @@ hledger-web - web interface for the hledger accounting tool | ||||
| hledger is a cross-platform program for tracking money, time, or any other commodity, | ||||
| using double-entry accounting and a simple, editable file format. | ||||
| hledger is inspired by and largely compatible with ledger(1). | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| 
 | ||||
| hledger-web is hledger's web interface.  It starts a simple web | ||||
|  | ||||
| @ -2,8 +2,10 @@ | ||||
| % | ||||
| % October 2015 | ||||
| 
 | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| <div class="man"> | ||||
| 
 | ||||
| # NAME | ||||
| 
 | ||||
| hledger - a command-line accounting tool | ||||
| @ -22,9 +24,6 @@ hledger aims to be a reliable, practical tool for daily use. This man | ||||
| page is a quick reference and introduction; for more complete docs, see | ||||
| http://hledger.org/manual. | ||||
| 
 | ||||
| </div> | ||||
| <div class="web"> | ||||
| * toc | ||||
| </div> | ||||
| 
 | ||||
| This is hledger’s command-line interface (there are also curses and web | ||||
|  | ||||
| @ -13,7 +13,10 @@ pre { | ||||
| 		/* display:table; */ | ||||
| 		/* background-color:#e0e0e0; */ | ||||
| } | ||||
| .clear, h3, h4, h5, h6 { | ||||
| .clear { | ||||
| 		clear:both; | ||||
| } | ||||
| h4, h5, h6 { | ||||
| 		clear:both; | ||||
| } | ||||
| .display-table { | ||||
| @ -70,11 +73,28 @@ pre { | ||||
| .navbar       { font-size:x-large;  } | ||||
| .navbar-brand { font-weight:bold; font-size:xx-large; } | ||||
| .navbar-nav   { margin-left:1em;  } | ||||
| /* from https://github.com/blaenk/blaenk.github.io/blob/source/provider/scss/_article.scss */ | ||||
| /* table of contents styling */ | ||||
| /* based on https://github.com/blaenk/blaenk.github.io/blob/source/provider/scss/_article.scss */ | ||||
| #toc { | ||||
| 		max-width:40%; | ||||
|     margin-top: 1em; | ||||
| } | ||||
| /* move it to the right */ | ||||
| #toc { /* right */ | ||||
|     float: right; | ||||
| 		margin:0 0 2em 2em; | ||||
|     padding: 0; | ||||
| } | ||||
| #toc (@media screen and (max-width: 600px)) { | ||||
| 		float: none; | ||||
| 		padding: 0; | ||||
| 		margin-left: 0; | ||||
| 		margin-top: 10px; | ||||
| } | ||||
| #toc:after { | ||||
| 		clear: both; | ||||
| } | ||||
| /* margins and fonts */ | ||||
| #toc p { | ||||
| 		font-weight: bold; | ||||
| 		margin-top: 0; | ||||
| @ -88,18 +108,9 @@ pre { | ||||
| 		padding-left:0; | ||||
| 		/* margin-left:1em; */ | ||||
| } | ||||
| #toc > ol > li > a { | ||||
| 		display:none; | ||||
| } | ||||
| #toc > ol (@media screen and (max-width: 600px)) { | ||||
| 		font-size: 13px; | ||||
| } | ||||
| #toc > ol ol { | ||||
| 		counter-reset: item; | ||||
| } | ||||
| #toc > ol > li > ol ol { | ||||
| 		font-size:95%; | ||||
| } | ||||
| #toc li { | ||||
| 		margin-top: 0; | ||||
| 		display: block; | ||||
| @ -107,32 +118,29 @@ pre { | ||||
| #toc li (@media screen and (max-width: 600px)) { | ||||
| 		line-height: 1.69; | ||||
| } | ||||
| #toc > ol > li > ol > li:before { | ||||
| 		content: counters(item, ".") ". "; | ||||
| 		counter-increment: item; | ||||
| /* shrink subitems */ | ||||
| #toc > ol > li > ol ol { | ||||
| 		font-size:95%; | ||||
| } | ||||
| #toc > ol > li > ol > li > ol > li { | ||||
| 		padding-left:2em; | ||||
| } | ||||
| #toc > ol > li > ol > li > ol > li > ol li { | ||||
| /* indent subitems */ | ||||
| #toc > ol > li > ol li { | ||||
| 		padding-left:1em; | ||||
| } | ||||
| #toc.right-toc { | ||||
|     float: right; | ||||
|     /* margin-left: 15px; */ | ||||
| 		margin:0 0 2em 2em; | ||||
|     padding: 0; | ||||
| } | ||||
| #toc.right-toc (@media screen and (max-width: 600px)) { | ||||
| 		float: none; | ||||
| 		padding: 0; | ||||
| 		margin-left: 0; | ||||
| 		margin-top: 10px; | ||||
| } | ||||
| #toc:after { | ||||
| 		clear: both; | ||||
| } | ||||
| /* hide top item(s) */ | ||||
| /* #toc > ol > li > a { display:none; } */ | ||||
| /* #toc > ol > li > ol > li { padding-left:0; } */ | ||||
| /* number top items */ | ||||
| /* #toc > ol { counter-reset: item; } */ | ||||
| /* #toc > ol > li:before { */ | ||||
| /* 		content: counters(item, ".") ". "; */ | ||||
| /* 		counter-increment: item; */ | ||||
| /* } */ | ||||
| /* #toc > ol > li > ol > li { */ | ||||
| /* 		padding-left:2em; */ | ||||
| /* } */ | ||||
| 
 | ||||
| /* */ | ||||
| 
 | ||||
| h2 { | ||||
| 		margin-top:1.5em; | ||||
| } | ||||
|  | ||||
| @ -1,5 +1,9 @@ | ||||
| <!-- hledger repo and http://hledger.org versions of this document are periodically bidirectionally synced --> | ||||
| 
 | ||||
| <style> | ||||
| #toc > ol > li > a { display:none; } | ||||
| #toc > ol > li > ol > li { padding-left:0; } | ||||
| </style> | ||||
| * toc | ||||
| 
 | ||||
| # Developer guide | ||||
|  | ||||
							
								
								
									
										17
									
								
								site/docs.md
									
									
									
									
									
								
							
							
						
						
									
										17
									
								
								site/docs.md
									
									
									
									
									
								
							| @ -37,11 +37,11 @@ Writing `some.sub.account` instead of `some:sub:account`. | ||||
| 
 | ||||
| **General info:** | ||||
| 
 | ||||
| #### [plaintextaccounting.org](http://plaintextaccounting.org) | ||||
| A comprehensive collection common resources and practices from the plain text accounting community | ||||
| 
 | ||||
| #### [More docs](more-docs.html) | ||||
| A few more useful links, eg on accounting, not yet moved to the above | ||||
| Some useful links, eg on accounting, not yet moved to... | ||||
| 
 | ||||
| #### [plaintextaccounting.org](http://plaintextaccounting.org) | ||||
| A comprehensive collection of resources and practices from the plain text accounting community | ||||
| 
 | ||||
| 
 | ||||
| 
 | ||||
| @ -53,7 +53,7 @@ A few more useful links, eg on accounting, not yet moved to the above | ||||
| #### [User Manual](manual.html) | ||||
| The hledger reference manual, all on one page. | ||||
| 
 | ||||
| Or, here is more or less the same manual organized as unix man pages (work in progress): | ||||
| Or, as man pages (work in progress): | ||||
| 
 | ||||
| <div style="padding-left:1em;"> | ||||
| 
 | ||||
| @ -83,7 +83,12 @@ Timeclock format, a sequence of clock-in/clock-out records. | ||||
| #### [hledger_timedot(5)](hledger_timedot.5.html) | ||||
| Timedot format, an alternative time logging format. | ||||
| 
 | ||||
| <div> | ||||
| **Combined:** | ||||
| 
 | ||||
| #### [All man pages](manual2.html) | ||||
| All hledger man pages on one web page. | ||||
| 
 | ||||
| </div> | ||||
| 
 | ||||
| </div> | ||||
| </div> | ||||
|  | ||||
| @ -1,3 +1,7 @@ | ||||
| <style> | ||||
| #toc > ol > li > a { display:none; } | ||||
| #toc > ol > li > ol > li { padding-left:0; } | ||||
| </style> | ||||
| * toc | ||||
| 
 | ||||
| # Frequently asked questions | ||||
|  | ||||
| @ -1,5 +1,9 @@ | ||||
| <!-- hledger.org and hledger repo versions last synced: 2014/5/1 --> | ||||
| 
 | ||||
| <style> | ||||
| #toc > ol > li > a { display:none; } | ||||
| #toc > ol > li > ol > li { padding-left:0; } | ||||
| </style> | ||||
| * toc | ||||
| 
 | ||||
| # hledger User Manual | ||||
|  | ||||
| @ -1,3 +1,7 @@ | ||||
| <style> | ||||
| #toc > ol > li > a { display:none; } | ||||
| #toc > ol > li > ol > li { padding-left:0; } | ||||
| </style> | ||||
| * toc | ||||
| 
 | ||||
| # More docs... | ||||
|  | ||||
| @ -1,8 +1,8 @@ | ||||
| <!-- A manual TOC showing less detail than the automatic one. --> | ||||
| <!-- Putting the dates last is preferred for readability, but they are first in the headings below since that nicely keeps them out of the anchor urls. --> | ||||
| <nav id="toc" class="right-toc"> | ||||
| <nav id="toc"> | ||||
| <p>Major releases:</p> | ||||
| <ul> | ||||
| <ol> | ||||
| <li><a href="#hledger-0.27">hledger 0.27 (2015/10/30)</a> | ||||
| <li><a href="#hledger-0.26">hledger 0.26 (2015/7/12)</a> | ||||
| <li><a href="#hledger-0.25">hledger 0.25 (2015/4/7)</a> | ||||
| @ -30,7 +30,7 @@ | ||||
| <li><a href="#hledger-0.3">hledger 0.3 (2009/01/17)</a> | ||||
| <li><a href="#hledger-0.2">hledger 0.2 (2008/11/23)</a> | ||||
| <li><a href="#hledger-0.1">hledger 0.1 (2008/10/15)</a> | ||||
| </ul> | ||||
| </ol> | ||||
| </nav> | ||||
| 
 | ||||
| # Release notes | ||||
|  | ||||
| @ -1,3 +1,7 @@ | ||||
| <style> | ||||
| #toc > ol > li > a { display:none; } | ||||
| #toc > ol > li > ol > li { padding-left:0; } | ||||
| </style> | ||||
| * toc | ||||
| 
 | ||||
| # hledger Step by Step | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user