aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--flake.lock30
-rw-r--r--latexfmt.hs71
2 files changed, 71 insertions, 30 deletions
diff --git a/flake.lock b/flake.lock
index 28b70f1..6041939 100644
--- a/flake.lock
+++ b/flake.lock
@@ -1,12 +1,15 @@
{
"nodes": {
"flake-utils": {
+ "inputs": {
+ "systems": "systems"
+ },
"locked": {
- "lastModified": 1644229661,
- "narHash": "sha256-1YdnJAsNy69bpcjuoKdOYQX0YxZBiCYZo4Twxerqv7k=",
+ "lastModified": 1710146030,
+ "narHash": "sha256-SZ5L6eA7HJ/nmkzGG7/ISclqe6oZdOZTNoesiInkXPQ=",
"owner": "numtide",
"repo": "flake-utils",
- "rev": "3cecb5b042f7f209c56ffd8371b2711a290ec797",
+ "rev": "b1d9ab70662946ef0850d488da1c9019f3a9752a",
"type": "github"
},
"original": {
@@ -17,11 +20,11 @@
},
"nixpkgs": {
"locked": {
- "lastModified": 1644539890,
- "narHash": "sha256-plaenLdLspbDinPM9ULYq15zyQybsYKDs1qiDiIzI8E=",
+ "lastModified": 1711357928,
+ "narHash": "sha256-HBqGlF3NwAkwisipX7lq3Y1fpXuiGPJ7VnjcU5eUfwQ=",
"owner": "nixos",
"repo": "nixpkgs",
- "rev": "2c320fd36cb284ad5767de8550e1dcffa8cfdad8",
+ "rev": "1b1c743525de9db9a4d0b86fc48f3c23177ac54f",
"type": "github"
},
"original": {
@@ -35,6 +38,21 @@
"flake-utils": "flake-utils",
"nixpkgs": "nixpkgs"
}
+ },
+ "systems": {
+ "locked": {
+ "lastModified": 1681028828,
+ "narHash": "sha256-Vy1rq5AaRuLzOxct8nz4T6wlgyUR7zLU309k9mBC768=",
+ "owner": "nix-systems",
+ "repo": "default",
+ "rev": "da67096a3b9bf56a91d16901293e51ba5b49a27e",
+ "type": "github"
+ },
+ "original": {
+ "owner": "nix-systems",
+ "repo": "default",
+ "type": "github"
+ }
}
},
"root": "root",
diff --git a/latexfmt.hs b/latexfmt.hs
index dc26a80..6c070fc 100644
--- a/latexfmt.hs
+++ b/latexfmt.hs
@@ -1,20 +1,23 @@
-{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings #-}
-import Control.Applicative
-import Control.Monad.State
-import Data.Attoparsec.Text hiding ( take )
-import Data.Char ( isAlpha
- , isDigit
- )
-import qualified Data.Text as T
-import qualified Data.Text.IO as T
-import Prelude hiding ( print
- , takeWhile
- )
+import Control.Applicative
+import Control.Monad
+import Control.Monad.State
+import Data.Attoparsec.Text hiding (take)
+import Data.Char
+ ( isAlpha,
+ isDigit,
+ )
+import qualified Data.Text as T
+import qualified Data.Text.IO as T
+import Prelude hiding
+ ( print,
+ takeWhile,
+ )
data Tokens = Wrd {unwrd :: T.Text} | Cmd T.Text | BSq [Tokens] | BCr [Tokens] | NL | Cmt T.Text | Nobs | IMath T.Text | Math T.Text | Verbatim Bool T.Text
- deriving Show
+ deriving (Show)
isCtrl x = not $ isAlpha x || isDigit x
@@ -29,13 +32,14 @@ toStr (Wrd w) = do
else print w
when (w == "(") suppress
when (T.last w == '.') printnl
-toStr (Cmd c) = if T.length c > 0 && isCtrl (T.head c) || T.length c == 1
- then print' $ "\\" `T.append` c
- else do
- printnl'
- when (c == "end") unindent
- print $ "\\" `T.append` c
- when (c == "begin") indent
+toStr (Cmd c) =
+ if T.length c > 0 && isCtrl (T.head c) || T.length c == 1
+ then print' $ "\\" `T.append` c
+ else do
+ printnl'
+ when (c == "end") unindent
+ print $ "\\" `T.append` c
+ when (c == "begin") indent
toStr (BSq ts) = do
print' "["
suppress
@@ -50,7 +54,7 @@ toStr (BCr ts) = do
mapM_ toStr ts
unindent
print' "}"
-toStr NL = printnl' >> printnl
+toStr NL = printnl' >> printnl
toStr (Cmt c) = do
print "%"
print' c
@@ -69,30 +73,49 @@ toStr (IMath m) = do
-- Tokeniser
ws = inClass " \t\n"
+
pad = takeWhile ws
+
token = nl <|> pad *> (nobs <|> verbatim <|> verbatimStar <|> math <|> cmd <|> bsq <|> bcr <|> cmt <|> wrd)
+
nobs = string "~" *> pure Nobs
+
nl = string "\n" *> takeWhile (inClass " \t") *> string "\n" *> pure NL
+
cmd :: Parser Tokens
cmd = Cmd <$> (string "\\" *> ((unwrd <$> wrd) <|> pure ""))
+
bsq = BSq <$> (string "[" *> many' token) <* pad <* string "]"
+
bcr = BCr <$> (string "{" *> many' token) <* pad <* string "}"
+
wrd = Wrd <$> takeWhile1 (notInClass " \t\n[]{}\\~")
+
cmt = Cmt <$> (takeWhile1 (== '%') *> takeWhile (/= '\n'))
+
math = oldmath <|> newmath <|> oldimath <|> newimath
+
oldmath = Math <$> (string "$$" *> takeWhile (/= '$')) <* string "$$"
+
newmath = Math . T.pack <$> (string "\\[" *> manyTill' anyChar (string "\\]"))
+
oldimath = IMath <$> (string "$" *> takeWhile (/= '$')) <* string "$"
+
newimath = IMath . T.pack <$> (string "\\(" *> manyTill' anyChar (string "\\)"))
+
verbatim = Verbatim False . T.pack <$> (string "\\begin{verbatim}" *> manyTill' anyChar (string "\\end{verbatim}"))
+
verbatimStar = Verbatim True . T.pack <$> (string "\\begin{verbatim*}" *> manyTill' anyChar (string "\\end{verbatim*}"))
-- indented printer
type Beginning = Bool
+
type Indent = Int
+
type SuppressSpace = Bool
+
data Printer = Printer Beginning SuppressSpace Indent T.Text
- deriving Show
+ deriving (Show)
print :: T.Text -> State Printer ()
print str = do
@@ -101,7 +124,7 @@ print str = do
then print' str
else do
let indent = T.pack . take (2 * i) $ repeat ' '
- str' = T.concat [s, if beg then indent else " ", str]
+ str' = T.concat [s, if beg then indent else " ", str]
put $ Printer False False i str'
-- force unindented
@@ -109,7 +132,7 @@ print' :: T.Text -> State Printer ()
print' str = do
(Printer beg _ i s) <- get
let indent = T.pack . take (2 * i) $ repeat ' '
- str' = T.concat [s, if beg then indent else "", str]
+ str' = T.concat [s, if beg then indent else "", str]
put $ Printer False False i str'
printnl :: State Printer ()