gallery/make-pages/BuilderQQ.hs

81 lines
2.7 KiB
Haskell
Raw Normal View History

2024-07-07 14:04:38 -04:00
{-# LANGUAGE PatternSynonyms, TemplateHaskell #-}
2020-07-24 09:20:10 -04:00
module BuilderQQ
(b, Builder, toStrictText, toLazyText, fromText, fromString,
ifJust, escId, escAttr, CanBuild (..))
2020-07-24 09:20:10 -04:00
where
2020-07-12 22:01:31 -04:00
import Data.Char (isSpace, isAlphaNum)
2020-07-12 22:01:31 -04:00
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Data.List (dropWhileEnd)
2022-12-30 16:00:13 -05:00
import Data.Maybe (mapMaybe, fromMaybe)
2020-07-12 22:01:31 -04:00
import Data.Text.Lazy.Builder
(Builder, fromText, fromLazyText, fromString, singleton, toLazyText)
import qualified Data.Text as Strict
import qualified Data.Text.Lazy as Lazy
2020-07-12 22:01:31 -04:00
import Data.Text.Lazy (toStrict)
import Data.List.NonEmpty (NonEmpty, toList)
2020-07-12 22:01:31 -04:00
data Chunk = Lit String | Var String
2020-07-12 22:01:31 -04:00
parseB :: String -> ExpQ
parseB = toExpQ . reverse . go "" [] . dropWhileEnd isSpace where
go acc cs [] = addLit acc cs
go acc cs ('$':'&':rest) = go acc cs rest -- $&: expands to nothing
go acc cs ('$':'$':rest) = go ('$' : acc) cs rest -- $$: expands to one $
go acc cs ('$':rest) = go "" (Var var : addLit acc cs) rest' -- $var
where (var, rest') = span isIdChar rest
go acc cs (c:rest) = go (c : acc) cs rest
2020-07-12 22:01:31 -04:00
addLit l cs = if null l then cs else Lit (reverse l) : cs
isIdChar c = isAlphaNum c || c `elem` ("_'" :: String)
2020-07-12 22:01:31 -04:00
toExpQ cs = [|mconcat $(listE $ mapMaybe chunk1 cs) :: Builder|]
chunk1 (Lit lit) = Just $ stringE lit
chunk1 (Var name) = Just $ [|build $(varE $ mkName name)|]
2020-07-12 22:01:31 -04:00
toStrictText :: Builder -> Strict.Text
2020-07-12 22:01:31 -04:00
toStrictText = toStrict . toLazyText
b :: QuasiQuoter
b = QuasiQuoter parseB undefined undefined undefined
2020-07-24 09:20:10 -04:00
2020-07-25 07:58:16 -04:00
ifJust :: Monoid b => Maybe a -> (a -> b) -> b
ifJust x f = maybe mempty f x
2020-08-03 13:37:44 -04:00
escId :: Strict.Text -> Builder
escId = foldMap esc1 . Strict.unpack where
2020-08-03 13:37:44 -04:00
esc1 c | isSpace c = ""
| latin1Special c = "_"
| otherwise = singleton c
2020-08-03 13:37:44 -04:00
latin1Special c =
c <= 'ÿ' && not (isAlphaNum c) && c /= '-'
escAttr :: Strict.Text -> Builder
escAttr = foldMap esc1 . Strict.unpack where
esc1 c = fromMaybe (singleton c) $ lookup c
[('<', "&lt;"), ('>', "&gt;"), ('"', "&quot;"), ('\'', "&apos;")]
2020-09-13 20:33:27 -04:00
class CanBuild a where build :: a -> Builder
instance CanBuild Builder where build = id
instance CanBuild Strict.Text where build = fromText
instance CanBuild Lazy.Text where build = fromLazyText
instance CanBuild Char where build = singleton
instance CanBuild String where build = fromString
newtype ShowBuild a = ShowBuild a deriving newtype Show
instance Show a => CanBuild (ShowBuild a) where build = build . show
deriving via ShowBuild Int instance CanBuild Int
deriving via ShowBuild Integer instance CanBuild Integer
instance {-# OVERLAPPABLE #-} CanBuild a => CanBuild [a] where
build = foldMap \x -> build x <> "\n"
2024-07-07 20:47:18 -04:00
instance CanBuild a => CanBuild (NonEmpty a) where build = build . toList