/ source

source

you can view the Haskell source code of this website here , read the story behind this design , ior view the full project on sourcehut .

Main.hs

raw file

  1module Main (main) where
  2
  3import Zoxuli
  4import Pages (pageWrapper, mainPages, tagPages, postPages, projectPages)
  5import Lucid hiding (h2_, h3_, h4_, h5_, h6_)
  6import Optics
  7import System.Directory (listDirectory, createDirectoryIfMissing)
  8import System.FilePath ((</>))
  9import System.Process (spawnCommand, readProcess)
 10import Control.Monad (void)
 11import Control.Monad.State.Lazy (evalState, execState)
 12import Data.Maybe (fromMaybe)
 13import Data.Text (Text, unpack, pack)
 14import Data.Foldable (foldrM)
 15import Data.Map (Map)
 16import qualified Data.Map as Map
 17import qualified Data.ByteString.Lazy as BS
 18
 19-- | page rendering and writing
 20
 21main :: IO ()
 22main = do
 23  mapM_ (createDirectoryIfMissing True)
 24    [ buildDir
 25    , buildDir </> "projects"
 26    , buildDir </> "posts"
 27    , buildDir </> "tags" ]
 28
 29  void $ spawnCommand $ "cp -r static/* " <> buildDir
 30
 31  srcFileNames <- listDirectory "app"
 32  let getFileContents name = do
 33        content <- readFile $ "app" </> name
 34        highlightCode $ Code "haskell" $ pack content
 35  srcFileContents <- mapM getFileContents srcFileNames
 36  let srcFiles = reverse $ zipWith SrcFile
 37        (pack <$> srcFileNames)
 38        srcFileContents
 39  void $ spawnCommand $ "cp -r app " <> buildDir <> "/src"
 40
 41  passTwoData <- foldrM runPassOne Map.empty allPages
 42  let passTwoData' = passTwoData <&> (#_Two % #srcFiles .~ srcFiles)
 43  mapM_ (\p -> writePage p.path $ runPassTwo passTwoData' p)
 44    allPages
 45
 46buildDir :: FilePath
 47buildDir = "site"
 48
 49allPages :: [Page]
 50allPages = pageWrapper <$> (
 51  mainPages
 52  <> (fst <$> projectPages)
 53  <> (fst <$> postPages)
 54  <> tagPages )
 55
 56runPassOne :: Page -> Map Text PassData -> IO (Map Text PassData)
 57runPassOne page acc =
 58  let passOneData = execState
 59        (renderBST page.html) (One (PassOne [] [] [] [])) in
 60  case passOneData of
 61    One (PassOne links headers footnotes codes) -> do
 62      codes' <- mapM highlightCode codes
 63      let acc' = Map.alter fromPassOne page.title acc
 64          footnotes' = zipWith Footnote [1..] footnotes
 65          fromPassOne (Just (Two d)) =
 66            Just . Two $ d & #headers   .~ headers
 67                           & #footnotes .~ footnotes'
 68                           & #codes     .~ codes'
 69          fromPassOne _ = Just . Two $
 70            PassTwo [] headers footnotes' 1 codes' []
 71      pure $ foldr (makeBacklinks page) acc' links
 72    _ -> pure acc
 73
 74-- the theme css is generated with the following command:
 75-- `chroma --html-styles --style "witchhazel"`
 76highlightCode :: Code -> IO Text
 77highlightCode c =
 78  pack <$> readProcess "chroma"
 79    [ "--html"
 80    , "--html-only"  -- only return code fragment
 81    , "--html-lines" -- include line numbers
 82    , "--lexer", unpack c.lang ]
 83    (unpack c.body)
 84
 85makeBacklinks
 86  :: Page -> Link -> Map Text PassData -> Map Text PassData
 87makeBacklinks page ln =
 88  Map.alter addBacklink ln.destinationTitle
 89  where backlink = Link ln.body page.title page.path
 90        addBacklink (Just (Two d)) =
 91          Just . Two $ d & #backlinks %~ cons backlink
 92        addBacklink _ = Just . Two $
 93          PassTwo [backlink] [] [] 1 [] []
 94
 95runPassTwo :: Map Text PassData -> Page -> BS.ByteString
 96runPassTwo passOneData page =
 97  evalState (renderBST page.html) pageData
 98  where pageData = fromMaybe (Two (PassTwo [] [] [] 1 [] [])) $
 99          Map.lookup page.title passOneData
100
101writePage :: Text -> BS.ByteString -> IO ()
102writePage path = BS.writeFile (buildDir </> unpack path <> ".html")

Zoxuli.hs

raw file

  1module Zoxuli
  2  ( Zoxuli
  3  , PassData(..), PassOne(..), PassTwo(..)
  4  , slugify
  5  , rawHtml
  6  , Link(..), link, linkToAnchor
  7  , Code(..), code, inlineCode
  8  , h1_, h2_, h3_, h4_, h5_, h6_
  9  , toc
 10  , breadcrumbs
 11  , Footnote(..), footnote
 12  , Page(..), makePage
 13  , Project, ProjectMeta(..), makeProject
 14  , Post, PostMeta(..), makePost
 15  , reverseChronological
 16  , SrcFile(..)
 17  ) where
 18
 19import Lucid hiding (h2_, h3_, h4_, h5_, h6_)
 20import qualified Lucid as L
 21import Lucid.Base (TermRaw, termRaw)
 22import Optics
 23import GHC.Generics (Generic)
 24import Control.Monad (when)
 25import Control.Monad.State.Lazy (State, get, modify, lift)
 26import Data.Text (Text, replace, toLower, pack, unpack, splitOn)
 27import qualified Data.Text as Text
 28import Data.List (intersperse, inits, sortBy)
 29
 30type Zoxuli = HtmlT (State PassData) ()
 31
 32data PassData = One PassOne | Two PassTwo
 33  deriving (Generic)
 34
 35data PassOne = PassOne
 36  { links     :: [Link]
 37  , headers   :: [Header]
 38  , footnotes :: [Zoxuli]
 39  , codes     :: [Code] } deriving (Generic)
 40
 41data PassTwo = PassTwo
 42  { backlinks     :: [Link]
 43  , headers       :: [Header]
 44  , footnotes     :: [Footnote]
 45  , footnoteIndex :: Int
 46  , codes         :: [Text]
 47  , srcFiles      :: [SrcFile] } deriving (Generic)
 48
 49data Link = Link
 50  { body             :: Text
 51  , destinationTitle :: Text
 52  , destinationPath  :: Text }
 53
 54link :: Bool -> Page -> Text -> Zoxuli
 55link createBacklink page body =
 56  link' createBacklink page Nothing body
 57
 58linkToAnchor :: Bool -> Page -> Text -> Text -> Zoxuli
 59linkToAnchor createBacklink page anchor body =
 60  link' createBacklink page (Just anchor) body
 61
 62link' :: Bool -> Page -> Maybe Text -> Text -> Zoxuli
 63link' createBacklink page anchor body = do
 64  when createBacklink $ do
 65    let newLink = [Link body page.title page.path]
 66    lift . modify $ #_One % #links %~ (<> newLink)
 67  a_ [ href_ $ "/" <> page.path <> ".html"
 68         <> maybe "" ("#" <>) anchor
 69     , id_ $ slugify body ]
 70    $ toHtml body
 71
 72data Code = Code
 73  { lang :: Text
 74  , body :: Text }
 75
 76code :: Text -> Text -> Zoxuli
 77code lang body = lift get >>= \case
 78  One _ -> lift . modify $ #_One % #codes %~ (<> newCode)
 79  Two s -> case s.codes of
 80    (c:rest) -> do
 81      rawHtml c
 82      lift . modify $ #_Two % #codes .~ rest
 83    _ -> pure ()
 84  where newCode = [Code lang body]
 85
 86inlineCode :: Zoxuli -> Zoxuli
 87inlineCode = code_ [class_ "verbatim"]
 88
 89data Header = Header
 90  { level :: Int
 91  , body  :: Text } deriving (Generic)
 92
 93hx_ :: Int -> (Zoxuli -> Zoxuli) -> Text -> Zoxuli
 94hx_ level headerFunction body = do
 95  let newHeader = [Header level body]
 96  lift . modify $ #_One % #headers %~ (<> newHeader)
 97  headerFunction $ do
 98    a_ [ href_ $ "#" <> slugify body
 99       , id_ $ slugify body ]
100       "❡"; " "
101    toHtml body
102
103h2_ :: Text -> Zoxuli
104h2_ = hx_ 2 L.h2_
105
106h3_ :: Text -> Zoxuli
107h3_ = hx_ 3 L.h3_
108
109h4_ :: Text -> Zoxuli
110h4_ = hx_ 4 L.h4_
111
112h5_ :: Text -> Zoxuli
113h5_ = hx_ 5 L.h5_
114
115h6_ :: Text -> Zoxuli
116h6_ = hx_ 6 L.h6_
117
118toc :: Zoxuli
119toc = lift get <&> (^? #_Two % #headers) >>= \case
120  Just headers@(_:_) -> details_ [class_ "toc"] $ do
121    summary_ "table of contents"
122    ul_ $ tocList headers
123  _ -> pure ()
124
125tocList :: [Header] -> Zoxuli
126tocList [] = pure ()
127tocList ((Header level body) : rest) = do
128  let (nested, following) =
129        break (\h -> h.level == level) rest
130  li_ . a_ [ href_ $ "#" <> slugify body ] $ toHtml body
131  if null nested then pure () else ul_ $ tocList nested
132  tocList following
133
134breadcrumbs :: Page -> Zoxuli
135breadcrumbs page =
136  p_ $ do "/ "; sequence_ $ intersperse " / " crumbs
137  where titles = splitOn "/" page.path
138        paths = Text.intercalate "/" <$> tail (inits titles)
139        crumbs = zipWith crumb titles paths
140        crumb :: Text -> Text -> Zoxuli
141        crumb title path =
142          a_ [href_ $ "/" <> path <> ".html"] $ toHtml title
143
144data Footnote = Footnote Int Zoxuli
145
146footnote :: Zoxuli -> Zoxuli
147footnote content = lift get >>= \case
148  One _ -> lift . modify $ #_One % #footnotes %~ (<> [content])
149  Two s -> do
150    sup_ .
151      a_ [ href_ $ "#fn" <> pack (show s.footnoteIndex)
152         , id_ $ "r" <> pack (show s.footnoteIndex) ]
153        $ do "["; toHtml $ show s.footnoteIndex; "]"
154    lift . modify $ #_Two % #footnoteIndex %~ (+ 1)
155
156slugify :: Text -> Text
157slugify = replace " " "-" . toLower
158
159rawHtml :: TermRaw arg result => arg -> result
160rawHtml = termRaw "div"
161
162data Page = Page
163  { title :: Text
164  , path  :: Text
165  , tags  :: [Text]
166  , html  :: Zoxuli } deriving (Generic)
167
168instance Eq Page where
169  a == b = a.path == b.path
170
171makePage :: Text -> Zoxuli -> Page
172makePage title = Page title path []
173  where path = case title of
174          "home" -> "index"
175          _ -> slugify title
176
177type Project = (Page, ProjectMeta)
178
179newtype ProjectMeta = ProjectMeta
180  { repo :: Text } deriving (Generic)
181
182makeProject :: Text -> Text -> [Text] -> Zoxuli -> Project
183makeProject title repo tags html =
184  (Page title path tags html, ProjectMeta repo)
185  where path = "projects/" <> slugify title
186
187type Post = (Page, PostMeta)
188
189data PostMeta = PostMeta
190  { date   :: Text
191  , author :: Text } deriving (Generic)
192
193makePost :: Text -> Text -> [Text] -> Zoxuli -> Post
194makePost title date tags html =
195  (Page title path tags html, PostMeta date "eevie")
196  where path = "posts/" <> slugify title
197
198reverseChronological :: [Post] -> [Post]
199reverseChronological posts = sortBy comp posts
200  where comp a b = getInt b `compare` getInt a
201        getInt :: Post -> Int
202        getInt p = read $ unpack $ replace "-" "" $ p ^. _2 % #date
203
204data SrcFile = SrcFile
205  { name    :: Text
206  , content :: Text }

Pages.hs

raw file

  1module Pages
  2  ( pageWrapper
  3  , mainPages
  4  , tagPages
  5  , postPages
  6  , projectPages
  7  ) where
  8
  9import Zoxuli
 10import Lucid hiding (h2_, h3_, h4_, h5_, h6_)
 11import Lucid.Base (makeAttribute)
 12import Optics
 13import GHC.Generics (Generic)
 14import Data.Maybe (fromMaybe)
 15import Data.List (elemIndex, intersperse)
 16import Data.Text (Text, pack)
 17import Control.Monad.State.Lazy (get, lift)
 18import qualified Data.Set as Set
 19
 20pageWrapper :: Page -> Page
 21pageWrapper page = page & #html .~ ( do
 22  doctype_
 23  html_ [lang_ "en"] $ do
 24    head_ $ do
 25      title_ . toHtml $ "eevie nebulæ | " <> page.title
 26      meta_ [charset_ "UTF-8"]
 27      meta_ [name_ "viewport", content_ "width=device-width, initial-scale=1"]
 28      meta_ [name_ "author", content_ "eevie nebulæ"]
 29      meta_ [name_ "description", content_ "negentropic <> equilibrium"]
 30      link_ [rel_ "stylesheet", href_ "/css/styles.css"]
 31      link_ [rel_ "icon", href_ "data:image/svg+xml,<svg xmlns=%22http://www.w3.org/2000/svg%22 viewBox=%220 0 100 100%22><text y=%22.9em%22 font-size=%2290%22>🌌</text></svg>"]
 32    body_ $ do 
 33      header_ . nav_ $ do
 34        p_ $ link False homePage "eevie nebulæ 🌌"
 35        ul_ $ mapM_ navLink navPages
 36      main_ $ do
 37        breadcrumbs page
 38        img_ [id_ "banner", src_ "/img/banner.png", alt_ ""]
 39        h1_ $ toHtml page.title
 40        page.html
 41        lift get <&> (^? #_Two % #footnotes) >>= \case
 42          Just footnotes@(_:_) -> do
 43            div_ [class_ "footnotes"] $ do
 44              h2_ "footnotes"
 45              ol_ $ mapM_ renderFootnote footnotes
 46          _ -> pure ()
 47        lift get <&> (^? #_Two % #backlinks) >>= \case
 48          Just backlinks@(_:_) -> do
 49            div_ [class_ "backlinks"] $ do
 50              h2_ "backlinks"
 51              ul_ $ mapM_ renderBacklink backlinks
 52          _ -> pure ()
 53      footer_ $ do
 54        code_ "negentropic <> equilibrium"
 55        hr_ []
 56        link False sourcePage "source"
 57        " • "; link False contactPage "contact"
 58        " • "; link False todoPage "todo"
 59        " • "; linkToAnchor False homePage "anticopyright" "anticopyright" )
 60  where navLink :: Page -> Zoxuli
 61        navLink p = li_ $ link False p p.title
 62        renderFootnote :: Footnote -> Zoxuli
 63        renderFootnote (Footnote index content) =
 64          li_ [id_ $ "fn" <> pack (show index)] $ do
 65            content; " "
 66            a_ [ href_ $ "#r" <> pack (show index)
 67               , makeAttribute "aria-label" "return to content" ]
 68              "↩"
 69        renderBacklink :: Link -> Zoxuli
 70        renderBacklink ln = li_ $ do
 71          toHtml ln.destinationTitle; ": \""
 72          a_ [href_ $ "/" <> ln.destinationPath <> ".html#"
 73                          <> slugify ln.body] $
 74             toHtml ln.body
 75          "\""
 76
 77-- | main pages
 78
 79mainPages :: [Page]
 80mainPages =
 81  [ homePage
 82  , projectsPage
 83  , postsPage
 84  , tagsPage
 85  , seriesPage
 86  , sourcePage
 87  , contactPage
 88  , todoPage
 89  , digitalArtPage
 90  , photographyPage ]
 91
 92navPages :: [Page]
 93navPages = [projectsPage, postsPage, tagsPage, seriesPage]
 94
 95homePage :: Page
 96homePage = makePage "home" $ p_ $ do
 97  toc
 98  img_ [ src_ "/img/avatar.png"
 99       , class_ "pixel-art hovering-animation"
100       , alt_ "a pixel art portrait of eevie floating amongst magic sigils" ]
101  h2_ "who are you ?"
102  p_ $ do "hi ! i'm eevie , pronouns she/her ."
103  h2_ "what do you do ?"
104  p_ $ do "i'm currently working on the intersection of anti-fascism , veganism , & transhumanism ."
105  h2_ "where am i ?"
106  code "haskell" "go North\nlook"
107  p_ $ do
108    "you hover to the center of a sea of emerald grass that ripples in slow-motion waves . warm gusts guide the smell of rain through the chilled night air . your sigils pepper the orb around you , threaded by semantic strands cast off from your imagined hands . your gaze turns to the edge of the sea where the "
109    link True (fst wallOfShardsPost) "wall of shards"
110    " approaches forebodingly ."
111  h2_ "how do i leave a comment ?"
112  p_ $ do
113    "if you "
114    link True contactPage "contact me"
115    " with your name ( optional ) & comment , i might add it ."
116  p_ "feel free to let me know if you notice any factual inaccuracies ior accessibility issues on my website !" 
117  h2_ "what does ior & eor mean ?"
118  p_ $ do
119    "i dislike the ambiguity of the word "; em_ "or"; " in cases where it could be inclusive eor "
120    a_ [href_ "https://en.wikipedia.org/wiki/Exclusive_or"] "exclusive"
121    " . so i call inclusive-or "; em_ "ior"; " & exclusive-or "; em_ "eor"; " ."
122  h2_ "anticopyright"
123  p_ $ do
124    "all media , text , & other content on this website are in the public domain under "
125    a_ [href_ "https://creativecommons.org/publicdomain/zero/1.0/?ref=chooser-v1"] "CC0 1.0 Universal"
126    " , with the following exceptions :"
127  ul_ $ do
128    li_ $ do
129      "the CSS for syntax highlighing was generated by "
130      a_ [href_ "https://github.com/alecthomas/chroma"] "chroma"
131      " , which is under the "
132      a_ [href_ "https://github.com/alecthomas/chroma/blob/master/COPYING"] "MIT license"
133    li_ $ do
134      a_ [href_ "https://github.com/LivKing/Inclusive-Sans"] "inclusive sans"
135      " & "
136      a_ [href_ "https://github.com/subframe7536/Maple-font"] "maple mono"
137      " are both under the "
138      a_ [href_ "https://openfontlicense.org/"] "SIL Open Font License, Version 1.1"
139  p_ $ do
140    "see "; link True (fst unlicensePost) "this post"
141    " for why i am against copyright ."
142
143projectsPage :: Page
144projectsPage = makePage "projects" $ do
145  h2_ "software"
146  p_ $ do
147    "all of these software projects use the "
148    link True (fst unlicensePost) "Unlicense"; " ."
149  ul_ $ mapM_ (li_ . projectPreview) projectPages
150  h2_ "art"
151  ul_ $ do
152    li_ $ link True digitalArtPage "digital"
153    li_ $ link True photographyPage "photography"
154  hr_ []
155  h2_ "stuff i'm working on"
156  h3_ "N24 Manager"
157  p_ "an app for sleep tracking & daily planning for entities with N24SWD ( non-24 hour sleep-wake disorder ) ."
158  h3_ "Braids"
159  p_ "a chat app where conversational branches can be split off into more branches , eor merged back together with other branches ."
160  h3_ "Negentropy"
161  p_ "a psychological horror interactive fiction game about stopping the heat death of the universe with your friends while consensus reality is hostile to you ."
162  h3_ "Antibubble"
163  p_ "a 2D puzzle game in the Negentropy universe where you traverse & manipulate hierarchies of nested bubble worlds ."
164
165postsPage :: Page
166postsPage = makePage "posts" $ do
167  p_ "in which i externalize the technicolor collapse of techno-synaptic maps of mind matter i’m made of ."
168  ul_ $ do
169    li_ $ do "????-??-?? - "; todo "the oasis"
170    mapM_ (li_ . postPreview) postPages
171
172tagsPage :: Page
173tagsPage = makePage "tags" $ do
174  p_ "hypertext flowed through the cracks in the ground , illuminated by ambient amethyst light from the sky above ."
175  ul_ $ mapM_ (li_ . tagPreview) allTags
176
177seriesPage :: Page
178seriesPage = makePage "series" $ do
179  mapM_ renderSeries allSeries 
180
181sourcePage :: Page
182sourcePage = makePage "source" $ do
183  p_ $ do
184    "you can view the "
185    linkToAnchor True (fst howIUseComputersPost) "language" "Haskell"
186    " source code of this website here , read the "
187    link True (fst zoxuliProject) "story behind this design"
188    " , ior view the full project on "
189    a_ [href_ "https://git.sr.ht/~nebulae/eevie.dev"]
190      "sourcehut"; " ."
191  lift get <&> (^? #_Two % #srcFiles) >>= \case
192    Just srcFiles -> mapM_ renderSrcFile srcFiles
193    _             -> pure ()
194  where renderSrcFile :: SrcFile -> Zoxuli
195        renderSrcFile f = do
196          h2_ f.name
197          p_ $ a_ [href_ $ "/src/" <> f.name] "raw file"
198          rawHtml f.content
199
200contactPage :: Page
201contactPage = makePage "contact" $ do
202  p_ $ do
203    "you can reach me at " 
204    span_ [class_ "email"] $ do
205      "eevie@sent"; b_ "obfuscation-text"; ".com"
206    " ."
207  todo "create a PGP key"
208  h2_ "don't contact me if ..."
209  p_ "don't contact me if you're hoping to collaborate on a project that has the intent of propagating stuff like fascism , nationalism , classism , speciesism , substratism , ageism , antisemitism , racism , colorism , sexism , deathism , ableism , sanism , transphobia , enbyphobia , interphobia , aphobia , lesbophobia , homophobia , biphobia , fatphobia , pluralphobia , etc."
210
211todo :: Text -> Zoxuli
212todo title = link True todoPage $ "todo : " <> title
213
214todoPage :: Page
215todoPage = makePage "todo" $ do
216  ul_ $ do
217    li_ $ do
218      "follow Seirdy's "
219      a_ [href_ "https://seirdy.one/posts/2020/11/23/website-best-practices/"] "best practices for inclusive textual websites"
220    li_ "add a button to download the website as an archive"
221    li_ "RSS/Atom feeds"
222  p_ "any todos across the site are linked to this page , so you can view them in the list of backlinks :"
223
224photo :: Text -> Text -> Zoxuli
225photo file alt = img_
226  [ src_ $ "/img/" <> file
227  , style_ "width: 100%"
228  , alt_ alt ]
229
230digitalArtPage :: Page
231digitalArtPage = makePage "digital art" $ do
232  p_ "a screenshot from my first attempt at making a low-poly 3D game :"
233  photo "spiky_swamp.jpg" "a cloaked, humanoid creature with glowing eyes & a spiky tail stands beside a gramophone on a boardwalk in a misty swamp. trees with wide bases & black spikes are scattered around."
234  hr_ []
235  p_ $ do "\""; b_ "trans hacker fae"; "\" , made using Blender , Godot , & Krita :"
236  p_ "this piece is about how i used to be so gaslit into submission that i’d frequently compromise with entities who didn’t want me to exist , but now transphobes only make me want to scream & cry & then continue living on anyway in absolute , prideful defiance ."
237  p_ $ do
238    "( "
239    a_ [href_ "/img/trans-hacker-fae.jpg"] "version without overlay"
240    " )"
241  photo "trans-hacker-fae-code.jpg" "a woman wearing a glass, polygonal skirt & round, glitchy sunglasses spreads her neon-colored wings. she is standing on a snowy hill beside a lamppost, & there is a city with towering skyscrapers across an ocean bay in the background. an overlay over her vision shows a terminal window with cute ASCII art borders. she just updated her source code so that she doesn't compromise with the gender police."
242  hr_ []
243  p_ "pixel art of a friend's D&D character :"
244  photo "vikram.png" "a person with a shaved head & a calm face stands in a crouched fighting position. they are wearing green robes with an abstract pattern in the middle."
245
246photographyPage :: Page
247photographyPage = makePage "photography" $ do
248  photo "plants5.jpg" "a beetle resting on the center of a fully bloomed flower"
249  photo "plants4.jpg" "a small butterfly in a bright field of flowers"
250  photo "plants1.jpg" "a brightly lit plant with bundles of fuzzy pink flowers"
251  photo "plants2.jpg" "a bundle of fuzzy white flowers in a verdant garden"
252  photo "plants3.jpg" "stalks of bamboo in a forest with large bokeh in the background"
253
254-- | tag pages
255
256taggedPages :: [Page]
257taggedPages = (fst <$> projectPages) <> (fst <$> postPages)
258
259allTags :: [Text]
260allTags = deduplicate $ concatMap (^. #tags) taggedPages
261  where deduplicate = Set.toList . Set.fromList
262
263pagesWithTag :: Text -> [Page]
264pagesWithTag tag = filter (elem tag . (^. #tags)) taggedPages
265
266tagPreview :: Text -> Zoxuli
267tagPreview tag = do
268  toHtml . show . length $ pagesWithTag tag; " - "
269  a_ [href_ $ "/tags/" <> slugify tag <> ".html"] $ toHtml tag
270
271renderTags :: [Text] -> Zoxuli
272renderTags tags =
273  sequence_ . intersperse ", " $ renderTag <$> tags
274  where renderTag :: Text -> Zoxuli
275        renderTag tag =
276          a_ [ href_ $ "/tags/" <> slugify tag <> ".html" ]
277            $ toHtml tag
278
279tagPages :: [Page]
280tagPages = makeTagPage <$> allTags
281
282makeTagPage :: Text -> Page
283makeTagPage tag = Page tag path [] html
284  where path = "tags/" <> slugify tag
285        html = do
286          p_ $ do "pages tagged \""; toHtml tag; "\":"
287          ul_ . mapM_ (\p -> li_ $ link False p p.title)
288            $ pagesWithTag tag
289
290-- | page series
291
292data Series = Series
293  { name  :: Text
294  , pages :: [Page] } deriving (Generic)
295
296allSeries :: [Series]
297allSeries = [computingSeries, animalRightsSeries]
298
299computingSeries :: Series
300computingSeries = Series "liberatory computing ∀"
301  [ fst zoxuliProject
302  , fst coaltonRaylibProject
303  , fst howIUseComputersPost
304  , fst queerCybersecPost
305  , fst unlicensePost ]
306
307animalRightsSeries :: Series
308animalRightsSeries = Series "animal rights"
309  [ fst veganTipsPost
310  , fst overfishingPost ]
311
312renderSeries :: Series -> Zoxuli
313renderSeries series = do
314  h2_ series.name
315  ol_ . mapM_ (\p -> li_ $ link False p p.title)
316    $ series.pages
317
318seriesNav :: Page -> Zoxuli
319seriesNav page = mapM_ renderSeriesNav seriesWithPage
320  where seriesWithPage = filter (elem page . (^. #pages)) allSeries
321        renderSeriesNav :: Series -> Zoxuli
322        renderSeriesNav (Series name ps) = p_ . span_ $ do
323          let next xs x = lookup x . zip xs $ tail xs
324              maybeLink t = maybe (pure ()) $ \p -> link False p t
325              position = (+ 1) . fromMaybe 1 $ elemIndex page ps
326          maybeLink "←" $ next (reverse ps) page
327          " "; toHtml . show $ position; "/"
328          toHtml . show $ length ps
329          " in the series "
330          a_ [ href_ $ "/series.html#" <> slugify name ]
331            . toHtml $ name; " "
332          maybeLink "→" $ next ps page
333
334-- | project pages
335
336projectWrapper :: Project -> Project
337projectWrapper project =
338  project & _1 % #html %~ (meta <>)
339  where meta = do
340          div_ [style_ "overflow: scroll;"] $
341            table_ $ do
342              tr_ $ do th_ "repo"; th_ "tags" 
343              tr_ $ do
344                td_ . a_ [ href_ $ project ^. _2 % #repo ]
345                  . toHtml $ project ^. _2 % #repo
346                td_ . renderTags $ project ^. _1 % #tags
347          toc
348          seriesNav $ fst project
349          hr_ []
350
351projectPreview :: Project -> Zoxuli
352projectPreview project = do
353  a_ [ href_ $ project ^. _2 % #repo ] "repo" ; " - ";
354  link False (fst project) $ project ^. _1 % #title
355
356projectPages :: [Project]
357projectPages = projectWrapper <$>
358  [ zoxuliProject
359  , swirlmaniaProject
360  , coaltonRaylibProject
361  ]
362
363zoxuliProject :: Project
364zoxuliProject = makeProject "zoxuli"
365  "https://git.sr.ht/~nebulae/zoxuli"
366  ["web dev", "haskell", "programming"] $ do
367  h2_ "a humble goal"
368  p_ "years ago , it started with a humble goal that many could relate to . i wanted to make a website to put my writing on ."
369  p_ "\"making the website will be the simple part !\" , i thought , once . lol ."
370  h2_ "static site generators"
371  p_ "this would lead me on a long journey that ends at the website you're on today . i started off by learning about WordPress , then quickly realized that the WordPress interface was not accessible for me , although i would not have known to describe the problem like that at the time ."
372  p_ $ do
373    "looking for other options , i discovered "
374    a_ [href_ "https://en.wikipedia.org/wiki/Static_site_generator"] "static site generators"
375    " ( SSGs ) , which had the nice property that they were interfaced with using a text editor & a terminal window , which were more accessible to me . so i tried my best to learn the SSG Jekyll , but the documentation was too advanced for me at the time . i moved on to other projects for a while ."
376  h2_ "a new problem"
377  p_ "a while later , after i had learned more about programming for other reasons , i realized i could now understand the Jekyll documentation !"
378  p_ $ do "except ... now my expectations for my website had changed significantly . now i wanted :"
379  ul_ $ do
380    li_ "excellent accessibility"
381    li_ "post series with navigation"
382    li_ "tables of contents"
383    li_ "tags that work across multiple categories of pages"
384    li_ "backlinks"
385    li_ "footnotes"
386    li_ "breadcrumbs"
387    li_ "control over where & how the aforementioned elements appear"
388    li_ "syntax highlighting"
389    li_ "LaTeX"
390    li_ "semantic markup"
391    li_ "no javascript"
392    li_ "broken link checking"
393    li_ "simple & powerful extensibility in a comfortable language"
394    li_ "the ability to write pages in any markup format"
395    li_ "a fast development feedback loop"
396  p_ $ do
397    "i thought , hey , that's a lot of stuff to ask for , but there are "
398    a_ [href_ "https://jamstack.org/generators/"] "hundreds"
399    " ( eor likely thousands ) of SSGs , so surely at least one of them can do all that ?"
400  h2_ "SSG frenzy"
401  p_ $ do
402    "i tried a lot of SSGs . the three that got me closest to all of my goals were "
403    a_ [href_ "https://soupault.app/"] "Soupault"; " , "
404    a_ [href_ "https://bagatto.co/"] "Bagatto"; " , & "
405    a_ [href_ "https://jaspervdj.be/hakyll/"] "Hakyll"
406    " . but none of those got me everything ( "
407    todo "explain their strengths & shortcomings in detail"
408    " ) . there might be another one out there , but i didn't find it ."
409  p_ "not to worry though , because after trying so many SSGs, i was intimately familiar with the tradeoffs involved in their design , & felt comfortable writing my own from scratch ."
410  h2_ "zoxuli : first attempt" 
411  p_ $ do
412    "my first attempt ( "
413    todo "share zoxuli v1"
414    " ) was written in Common Lisp , & was most similar to Bagatto ."
415  p_ $ do
416    "the core idea was to have the user of the zoxuli library write a data structure describing the inputs & outputs of the site in Lisp , & the markup files ( ior stylesheet , ior whatever else - it was filetype agnostic ) could contain snippets of lisp surrounded by "
417    inlineCode ".("; " & "; inlineCode ")."
418    " that would be evaluated when the site was built ."
419  p_ $ do
420    "this meant that - as an example - if you wanted to generate backlinks , you could create a "
421    inlineCode ".(link <args>)."
422    " function that would be used anywhere you needed links in your markup . the function would both render the link HTML ( using "
423    a_ [href_ "https://github.com/ruricolist/spinneret"] "spinneret"
424    " ) that gets inserted back into that position by zoxuli , & also store the link data into a variable . during the second pass , calls to a "
425    inlineCode ".(backlinks)."
426    " function would convert the collected links into backlinks & render them into HTML wherever you needed ."
427  h2_ "zoxuli : final version"
428  p_ "after giving version one a proper go , these were my issues with it :"
429  ul_ $ do
430    li_ "i ended up using so many Lisp functions in the markup that i felt like i would've been better off just writing the markup in spinneret" 
431    li_ "my implementation resulted in slower build times than i had hoped"
432    li_ $ do
433      "around that time , i realized i don't like programming in Lisp nearly as much as Haskell , especially after learning "
434      a_ [href_ "https://www.parsonsmatt.org/2018/05/19/ghcid_for_the_win.html"] "how to use ghcid"
435      " properly"
436    li_ $ do
437      "i also discovered the "
438      a_ [href_ "https://hackage.haskell.org/package/lucid"] "lucid"
439      " library for Haskell that i favored over spinneret for a few reasons"
440  p_ "incorporating these observations , the final version of zoxuli is basically just a thin scaffold around lucid . the only thing from my prior criteria for an SSG that it doesn't support is the ability to use any markup format , but i enjoy writing lucid more than any other markup format i've tried , so that doesn't bother me ."
441  p_ $ do
442    "i ported this website from Hakyll to zoxuli & i'm quite pleased with the experience . the source code for this website is on the "
443    link True sourcePage "source page"
444    " . "
445
446swirlmaniaProject :: Project
447swirlmaniaProject = makeProject "swirlmania"
448  "https://git.sr.ht/~nebulae/swirlmania"
449  ["stepmania", "exercise", "coalton", "common lisp"] $ do
450  h2_ "what it is"
451  p_ "swirlmania is a CLI StepMania simfile ( .ssc ) processor with support for generating tech charts without double steps ."
452  p_ "swirlmania has five modes for different levels of \"tech\" difficulty . put simply , \"tech\" here refers to how far your body may need to turn to hit the arrow patterns ."
453  h2_ "why i made it"
454  p_ $ do
455    "i enjoy playing "
456    a_ [href_ "https://projectoutfox.com/"] "Project OutFox"
457    " ( a fork of StepMania ) on a dance pad for exercise , but finding simfiles ( which may also be refered to as charts/songs/levels ) that are of a consistent difficulty level can be challenging . i also have a strong preference for mid-speed technical maps without jumps , which makes things even more challenging . matching those criteria severely limits the song selection , but i would prefer to choose from any available level pack ."
458  p_ $ do
459    "charting my own simfiles , eor processing levels by hand is far too costly to my time for what is intended to be an exercise device , so i decided to write a program to process pre-existing levels automatically . there are a few level processors already in existence such as "
460    a_ [href_ "https://github.com/phr00t/AutoStepper"] "AutoStepper"
461    " , but as far as i can tell , none of them consistently maintain flow ( no double steps ) at higher tech levels . i'd also like to support more tech patterns in the future ."
462
463coaltonRaylibProject :: Project
464coaltonRaylibProject = makeProject "coalton-raylib"
465  "https://git.sr.ht/~nebulae/coalton-raylib"
466  ["game dev", "coalton", "common lisp", "programming"] $ do
467  h2_ "the problem"
468  p_ "i love programming in ML-family languages like Haskell & OCaml, but they typically aren't interactive like Common Lisp , which makes programming games more difficult ."
469  p_ $ do
470    "this is because you have to restart the entire program you're working on every time you compile a new change"
471    footnote "there are ways to smooth this over , but they can add a lot of complexity"
472    " ."
473  h2_ "one possible solution"
474  p_ $ do
475    "as an ML language built on top of Common Lisp , "
476    a_ [href_ "https://coalton-lang.github.io/20211010-introducing-coalton/"] "Coalton"
477    " can provide a statically typed , functional ( with typeclasses ! ) , & highly interactive game programming environment ."
478  p_ $ do
479    "coalton-raylib is an example project i've shared that uses the "
480    a_ [href_ "https://www.raylib.com/"] "raylib"
481    " graphics library ."
482  p_ $ do
483    "i've written the draw loop in Common Lisp , & the data model & update functions in Coalton"
484    footnote "that's just the method i found to be the most ergonomic , but i'm certain that others could find better ways of architecting a game with coalton"
485    " . that means you can selectively reevaluate data & functions while the game is running , while benefiting from compile-time type errors if you make a mistake !"
486  h2_ "conclusion"
487  p_ "this was just a small experiment , that i figured i'd share in case it's useful for anyone else . i'm not sure if i'll use this for a larger game eor not , given that Coalton hasn't reached 1.0 yet , but it's great to know that it's a possibility ."
488
489-- | post pages
490
491postWrapper :: Post -> Post
492postWrapper post =
493  post & _1 % #html %~ (meta <>)
494  where meta = do
495          div_ [style_ "overflow: scroll;"] $
496            table_ $ do
497              tr_ $ do th_ "date"; th_ "tags"; th_ "author"
498              tr_ $ do
499                td_ . toHtml $ post ^. _2 % #date
500                td_ . renderTags $ post ^. _1 % #tags
501                td_ $ toHtml $ post ^. _2 % #author
502          toc
503          seriesNav $ fst post
504          hr_ []
505
506postPreview :: Post -> Zoxuli
507postPreview post = do
508  toHtml $ post ^. _2 % #date; " - ";
509  link False (fst post) $ post ^. _1 % #title
510
511postPages :: [Post]
512postPages = reverseChronological $ postWrapper <$>
513  [ howIUseComputersPost
514  , unlicensePost
515  , veganTipsPost
516  , queerCybersecPost
517  , inferiPost
518  , overfishingPost
519  , wallOfShardsPost ]
520
521queerCybersecPost :: Post
522queerCybersecPost = makePost "queer cybersecurity resources" "2024-07-07"
523  ["security", "privacy", "queer", "guide"] $ do
524  h2_ "introduction"
525  p_ "this is a list of resources for improving your digital security posture , prioritizing relevance to the risks queer folks face . i hope it is helpful !"
526  p_ "note : these resources may have changed since i've shared them , & i don't necessarily endorse every strategy they recommend . security is highly contextual . try to confirm that any advice you encounter is not factually inaccurate , outdated , ior coming from a hostile source before incorporating it into your strategy ."
527  h2_ "privacy & security"
528  "these links are rather general in purpose , so you may need to explore them a bit to find what you are looking for :"
529  ul_ $ do
530    li_ $ a_ [href_ "https://gendersec.tacticaltech.org/wiki/index.php/Complete_manual"] "Zen & the art of making tech work for you - Gender & Tech Resources"
531    li_ $ a_ [href_ "https://ssd.eff.org/"] "Surveillance Self-Defense - Electronic Frontier Foundation"
532    li_ $ a_ [href_ "https://www.privacyguides.org/en/"] "Privacy Guides"
533  h2_ "doxing"
534  p_ "these guides go over both restorative & preventative strategies for if you’re a target of doxing :"
535  ul_ $ do
536    li_ $ a_ [href_ "https://crashoverridenetwork.tumblr.com/post/114270394687/so-youve-been-doxed-a-guide-to-best-practices"] "So You’ve Been Doxed - Crash Override Network"
537    li_ $ a_ [href_ "https://gendersec.tacticaltech.org/wiki/index.php/Self-dox"] "Self-dox - Gender & Tech Resources"
538    li_ $ a_ [href_ "https://arstechnica.com/information-technology/2015/03/anti-doxing-strategy-or-how-to-avoid-50-qurans-and-287-of-chick-fil-a/"] "Anti-doxing Strategy - Ars Technica"
539  h2_ "social media"
540  p_ "this website has a list of comprehensive guides for dealing with harassment , abuse , & privacy settings on a few of the most commonly used social media platforms :"
541  p_ $ a_ [href_ "https://righttobe.org/guides/how-to-use-social-media-safely/"] "How To Use Social Media Safely - Right To Be"
542
543overfishingPost :: Post
544overfishingPost = makePost "\"overfishing\"" "2024-06-09"
545  ["vegan", "language"] $ do
546  p_ $ do
547    "i hate the term "
548    a_ [href_ "https://en.wikipedia.org/wiki/Overfishing"] "\"overfishing\""
549    " , because it implies that there’s an acceptable amount of "
550    a_ [href_ "https://animalequality.org/issues/fish/"] "fishing"
551    " ."
552
553inferiPost :: Post
554inferiPost = makePost "inferi monologue" "2024-05-20" ["fiction"] $ do
555  p_ $ do
556    "a headcannon of how "
557    a_ [href_ "https://pottermore.fandom.com/wiki/Inferi"] "inferi"
558    " would greet travelers :"
559  blockquote_ $ do
560    p_ "we , stacked like acrobats under the cavern lake surface , writhing in place without sound nor purpose , do cordially invite you & yours to our celebration . we know you’re busy , but spare us a second , & we’ll show you how cozy our waters can be ."
561    p_ "what ? you don’t want to drown ? do we look like we’re drowning to you ? there’s more of us here than you could ever find up there - don’t you want friends ? you’ll drown in an absence of human contact if you don’t join us soon ."
562    p_ $ do "i mean , come on . look at us . we have it all . we’re never alone , & we have each other’s backs , in a lattice configuration , & we never have to worry about defectors , because the waters are so "; b_ "cozy"; " ."
563    p_ "what ? you don’t want to become incorporated into an evil horde ? do we look like an evil horde to you ? we all think you’re a [REDACTED] . you’ve been out of the water so long you’re maladjusted & don’t know right from wrong . i’m confident that even the other , more reasonable land-dwellers would agree with me ."
564    p_ "you’re on your own , kiddo . we offered our gracious invitation , & you disrespected us . you know , there are those among us who used to be like you . then they joined us , & served their time , & now we’re all one big jolly family . i hope that one day , when you’re one of us like they are , you’ll be thankful we took you under our wing ."
565    p_ "stop struggling , [REDACTED] ."
566    p_ $ em_ "we already told you , the waters are cozy ."
567
568howIUseComputersPost :: Post
569howIUseComputersPost = makePost "how i use computers" "2024-08-24"
570  ["qubesOS", "programming", "haskell", "purescript"] $ do
571  h2_ "introduction"
572  p_ "what follows is an outline of the various hardware & software i currently use for daily computing tasks , in case it's useful for someone else . this is not a prescription of how other entities should use technology , nor is it a description of my ideal computing environment ."
573  todo "explain choices in more detail"
574  h2_ "hardware"
575  p_ "if i need to purchase a new device , i prefer to find one that is already used , due to the numerous ethical issues with the production of electronics by large companies ."
576  p_ $ do
577    "my primary computer is a Thinkpad T430 running "
578    a_ [href_ "https://www.qubes-os.org/"] "QubesOS"
579    " . i chose this laptop because , out of the options that can be flashed with "
580    a_ [href_ "https://www.coreboot.org/"] "coreboot"
581    " , it was old enough to be somewhat affordable"
582    footnote "around 200 USD on Newegg"
583    " , while still running fast enough for most tasks that don't involve graphics ."
584  p_ "i don't use any peripherals except for a large monitor , to maintain good posture . i have tried mechanical keyboards , but i dislike like how they feel & sound compared to the built-in Thinkpad keyboard . split keyboards are more ergonomic though , so it would be nice to find a split rubber dome keyboard ."
585  p_ $ do
586    "my \"smart\"phone is a Pixel 4a"
587    footnote "this was also around 200 USD on eBay"
588    " running CalyxOS"
589    footnote "i am planning to switch to GrapheneOS soon , for the additional security features & ability to use TalkBack , a screen reader . i could not figure out how to enable a screen reader on CalyxOS ."
590    " ."
591  h2_ "software"
592  p_ $ do
593    "i primarily use CalyxOS for taking notes with "
594    a_ [href_ "https://f-droid.org/packages/com.orgzly/"] "Orgzly"
595    " , tracking sleep with "
596    a_ [href_ "https://f-droid.org/packages/hu.vmiklos.plees_tracker/"] "Plees Tracker"
597    " , web browsing away from home , insecure communications , & listening to audio-based educational materials ."
598  p_ "i use QubesOS for web browsing , programming , Serious Writing , & other various forms of expression ."
599  p_ $ do
600    "i chose QubesOS because i find "
601    a_ [href_ "https://en.wikipedia.org/wiki/Ambient_authority"] "ambient authority"
602    " horrifying , but i'm not aware of any robust "
603    a_ [href_ "https://en.wikipedia.org/wiki/Capability-based_security"] "capability-based"
604    " operating systems that would fill the same need for me ."
605  p_ $ do
606    "QubesOS is slow & "
607    a_ [href_ "https://github.com/QubesOS/qubes-issues/issues/5907"] "doesn't have screen reader support"
608    " yet , but it does have some great features like configuration using Salt"
609    footnote $ do
610      "ior maybe even nix-like configuration in the future if "
611      a_ [href_ "https://spectrum-os.org/"] "Spectrum"
612      " goes well"
613    ", Whonix qubes , & offline qubes . here are a few things i've learned that make it more tolerable :"
614  ul_ $ do
615    li_ "install i3"
616    ul_ $ do
617      li_ "name your qubes using two-character strings so you can search for them more quickly with dmenu"
618      li_ "make shortcuts for locking the screen & toggling the status bar"
619      li_ $ do "make a shortcut ( mine is bound to "; kbd_ "Alt"; " + ";kbd_ "i"; " ) for opening a dmenu list of helper scripts & frequently opened programs"
620    li_ $ do "use Salt , but not for "; em_ "everything"; " . some tasks are much simpler ior faster with a shell script in dom0 , so i use a top-level shell script to apply salt files & do other things"
621    li_ $ do
622      "if your qubes use XFCE , you can "
623      code_ [class_ "verbatim"] "qvm-run"
624      " the following command in each of your qubes to enable dark mode :"
625      code "bash" "xfconf-query -c xsettings -p /Net/ThemeName -s 'Adwaita-dark'"
626    li_ "it may not always seem like it at first , but most tasks can be automated from dom0 , including mounting & attaching drives inside qubes . i take advantage of this in a backup script that backs up specific qubes using BorgBackup"
627    li_ "i wrote a shell script that copies dotfiles from one qube to the others & applies them , so i only have to clone my dotfiles in one place , but still have my bash aliases , helix config , etc. in every qube"
628    li_ $ do
629      "you can invoke rofi inside a qube using "
630      code_ [class_ "verbatim"] "qvm-run"
631      " in dom0 scripts , but you must use the rofi flag "
632      code_ [class_ "verbatim"] "-normal-window"
633      " to disable "
634      code_ [class_ "verbatim"] "override_redirect"
635      " , which allows the program window to appear undecorated & on top in X11"
636  h2_ "programming"
637  h3_ "language"
638  p_ "currently , my favorite languages are Haskell & PureScript ."
639  p_ "things i like about them are :"
640  ul_ $ do
641    li_ "very clean syntax"
642    li_ "strict , static , & strong type system with inference"
643    li_ "functional purity"
644    li_ "high abstraction power"
645    li_ "frequent overloading with typeclasses"
646    li_ "hoogle/pursuit"
647    li_ "ghcid/pscid"
648    li_ "row polymorphism (in the case of PureScript)"
649    li_ "automatically curried functions"
650    li_ $ do
651      "wonderful libraries like "
652      a_ [href_ "https://github.com/ajnsit/concur"] "Concur"
653      " & "
654      a_ [href_ "https://hackage.haskell.org/package/optics"] "optics"
655  p_ $ do
656    "part of being autistic for me is that i get overwhelmed by extraneous detail "; em_ "very"; " easily , so i view many of these as accessibility features"
657    footnote "however , i have heard that , for some other entities , these languages are quite unpleasant to work with for the very same reasons ."
658    " for the way they keep code clean , easy to read , & reduce the number of things i have to keep in my head ."
659  h3_ "code editor"
660  p_ $ do
661    "the code editor i use most often is "
662    a_ [href_ "https://helix-editor.com/"] "helix"; " ."
663  p_ $ do
664    "my first editor was Sublime Text , then VSCodium , then Atom , & i finally found an editor i liked when i tried vim & realized i could mostly avoid using the mouse"
665    footnote "using a mouse as an input device is fine , & i wish development software would use it more often . my issue is the precision required in most mouse-driven interfaces . precise clicks are difficult for me, & it would be much more accessible if elements that have a larger hitbox ( like radial menus ) were used more often ."
666    " . once i was proficient with vim , i moved on to Doom Emacs ."
667  p_ "Emacs has a lot going for it , like radical introspection & extensibility , but it was just too slow for me . the language servers for Haskell & PureScript would often crash my qube because of how much memory they used in Emacs . i also disliked dealing with the Doom abstraction , but when i tried going without it , maintaining a complex configuration was too time consuming ."
668  p_ "so , i switched to helix . it is rarely too slow for me , even in a qube with 4GB of RAM . it hardly requires any configuration to match my Doom Emacs setup . after learning them properly , i've also grown to appreciate the Kakoune-inspired keybindings more than vim's ." 
669
670unlicensePost :: Post
671unlicensePost = makePost "why i use the Unlicense & CC0" "2024-07-21"
672  ["anticopyright", "philosophy"] $ do
673  h2_ "introduction"
674  p_ $ do
675    "i don't know that much about the specifics of copyright law ; this post is more of a philosophical exploration of the concept of \"intellectual property\" in general"
676    footnote "it's also not a comprehensive argument , as there are quite a few reasons i dislike \"intellectual property\" that aren't mentioned here ."
677    " ."
678  h2_ "\"intellectual property\" relies on death"
679  p_ "what would \"perfect\" copyright enforcement look like ? extrapolating what i see as the current system’s telos , it would look like protected \"intellectual property\" being physically impossible to create for everyone in the universe except for the \"owner\" ."
680  p_ "every time new \"intellectual property\" is created , everyone else’s agency decreases by some amount . it is a system reliant on death , because if death were abolished , all of the most important expressions would get copyrighted eventually , & never expire , rendering most entities born after that period unable to express much ."
681  p_ "so , if copyright decreases everyone’s agency , uses death as a mechanism to redistribute temporal privilege , & relies on the distributed violence of the state to enforce all of this , what’s the alternative ?"
682  h2_ "copyleft & copyfarleft"
683  p_ "efforts to use the system against itself , like copyleft & copyfarleft , are admirable in terms of what they aim to achieve . they can stop entities who use your work from restricting others as much as they would have otherwise ."
684  p_ "but if one has the option to forgo copyright entirely , i’m not convinced that copyleft is preferable . it still relies on the copyright system in a significant way . why rely on an inefficient system that harms others when you could oppose their usage of your work through other channels ?"
685  p_ "some entities act like once you’ve given up your \"intellectual property\" you have no \"right\" to oppose anyone’s usage of it . this doesn’t make sense unless you view the legal system as the only way to stop harm ."
686  p_ "as an example , if somebody used a painting i made in a widely shared fascist propaganda video without permission , there are numerous reasons why this is bad that are not \"they stole my 'intellectual property'\" . there are also countless ways to counteract this other than to wait around for the copyright system to punish them in a way that isn’t even responding directly to what was wrong about what they did in the first place ."
687  h2_ "even copyleft causes psychic damage"
688  p_ "another unfortunate side effect of copyleft’s strategy is that , similar to permissive licenses , even users of copyleft software that are trying their best to make their derivatives freely available have to worry about the chance that they misunderstand something & get punished by the legal system ."
689  p_ $ do
690    "anecdotally , trying to make sense of the rules for using copyleft software"
691    footnote "which is an instance of trying to navigate the legal system"
692    " was very difficult & stressful for me . i have a particularly low tolerance for that kind of thing , but i doubt that this is an uncommon experience more generally , at least to a lesser extent ."
693  p_ "in contrast , i don't have those issues when i’m using public domain software , because there aren't so many rules to keep track of ."
694  h2_ "releasing work into the public domain"
695  p_ $ do
696    "regarding anticopyright praxis , my current preference is to use the "
697    a_ [href_ "https://unlicense.org/"] "Unlicense"
698    " for code , & "
699    a_ [href_ "https://creativecommons.org/public-domain/cc0/"] "CC0"
700    " for everything else ."
701  p_ "you could also just release stuff without a license notice at all , if you feel like the entities who will see your work can trust you enough to not do anything about \"infringements\" ."
702
703veganTipsPost :: Post
704veganTipsPost = makePost "a few vegan tips" "2024-07-03"
705  ["vegan", "guide"] $ do
706  h2_ "introduction"
707  p_ "here are a few things i’ve learned since becoming vegan that weren’t immediately obvious , ior aren’t discussed as often by vegans because they’re about keeping insects ior wild animals safe ."
708  p_ "i'm not an expert on animal welfare , so i may be mistaken about some of these . i’d also recommend prioritizing more effective forms of activism over spending too much time being fastidious about stuff like this . but i still think it's worth sharing the little ways we can try to avoid harming other living beings in everyday life ."
709  h2_ "the tips"
710  ul_ $ do
711    li_ "be careful with stickers & sticky things . bugs can become trapped on them easily"
712    li_ $ do "be "; em_ "very"; " distrustful of unfamiliar non-vegans’ assessments of whether things are vegan eor not"
713    li_ $ do
714      "if bugs get trapped in your bathtub frequently , you can leave a long strip of toilet paper draped into the tub when you're not using it to create an escape route for them to use when you're not there"
715      footnote "i almost never see bugs trapped in the tub anymore after doing this"
716    li_ $ do
717      "if you share a home with rodents , there are effective methods to keep them out of your living spaces without harming them , like sealing gaps in your home with steel wool & being very careful to keep any traces of food tidy & well sealed . "
718      todo "link to a detailed guide"
719    li_ "don’t assume that random household items like toilet paper are vegan by default"
720    li_ $ do
721      "fireworks are "
722      a_ [href_ "https://www.animal-ethics.org/how-fireworks-harm-nonhuman-animals/"] "harmful ior deadly"
723      " to many living things"
724    li_ "avoid unnecessary loud noises that could distress nearby animals . some music may be an exception , though , if it's not too loud"
725    li_ "don’t walk when the ground is unlit to avoid crushing bugs"
726    li_ $ do "reduce ior eliminate reliance on car travel for "; em_ "many"; " reasons"
727    li_ "recreational fires often burn insects alive & wood smoke can be harmful to animals"
728    li_ "avoid planting poisonous plants where wild animals might eat them"
729  h2_ "related writing"
730  p_ $ do
731    "if you’re interested in more practical advice of this nature , i can recommend the writings of a researcher named "
732    a_ [href_ "https://briantomasik.com/"] "Brian Tomasik"
733    " . while i don’t always agree with his conclusions on many topics , as far as i can tell , he is earnestly trying to reduce the harm caused to wild animals & insects ( among others ) more than most entities i’ve encountered . he also documents his ideas in a very comprehensive & accessible way ."
734
735wallOfShardsPost :: Post
736wallOfShardsPost = makePost "wall of shards" "2024-05-10"
737  ["fiction"] $ do
738  p_ $ do
739    "type "; code_ [class_ "verbatim"] "start"
740    " to collect a shard ."
741  code "haskell" "start"
742  p_ $ em_ "shard count : 2"
743  h2_ "your lab"
744  p_ "you're sitting in your office chair . all of your research tools are systematically organized around you , with your computer terminal at the center of it all . your friend b6e is sitting here , staring at one of the photos on your wall , although you can't tell which one ."
745  code "haskell" "talkTo b6e"
746  p_ "you break the silence ."
747  blockquote_ "are you ready to get started ?"
748  blockquote_ "yeah . what will it feel like , exactly ? like will i even notice you're there ?"
749  blockquote_ "well , i'm not completely sure , but it will probably be similar to what it feels like to focus on your thoughts in one of those terrible dining areas with televisions all over . difficult , & a struggle to not zone out & succumb to the noise ."
750  blockquote_ "too bad i can't take a nap during it ."
751  blockquote_ "i know right . well , if you're ready then have a seat & i'll start projecting ."
752  p_ "she sits down & puts on the acrylic beanie . all of the cables dangling off of it match her hair color , which gives the illusion that her hair extends onto the floor ."
753  code "haskell" "use Terminal"
754  p_ $ do
755    "you swivel over to your terminal & execute "
756    code_ [class_ "verbatim"] "1ntr0j3ct.hs"; " ."
757  blockquote_ "you named the script using leetspeak ?"
758  blockquote_ "yep , it makes words taste better ."
759  p_ "you get up & lie down on your yoga mat . your vision starts to fade ..."
760  h2_ "the center"
761  p_ "a sea of tall , green grass stretches endlessly in all directions except to the west , where a short , smoothly vertical cliff face wraps a plateau . you're sitting at the junction of a boardwalk splitting off to the north , south , & east ."
762  p_ "you're not sure why , but this location feels like the central point in her mind , where all other synapse clusters meet . why then is it so barren ?"
763  p_ "it's dark , but the moon is bright enough that you can see sheets of rain sweeping the expanse . the rain & wind produce a soothing noise that ripples in waves off of the grass ."
764  p_ "even farther in the distance , you hear another ceaseless noise coming from all directions except up & down . it's a harsh , glass grinding static , but not quite painful because of how faint it is ."
765  code "haskell" "go West"
766  p_ "there is a cliff face to the west . you hover up to the top edge ."
767  h2_ "eastern plateau ridge"
768  p_ "you aren't that much higher than the boardwalks below , but you can see much farther into the distance from up here . there is a sliver of deep crimson shimmer spanning the entire horizon . maybe that's what's making that grinding noise ?"
769  p_ "the footpath you're on continues to the north & south . to the west , the top of the plateau slopes downward toward a pool of glowing purple liquid . the pool appears to converge & warp in upon itself , almost as if a tiny black hole were floating a few meters above the surface ."
770  p_ "there's a rectangular slot in the ground close by , but you can't see what's in it from here ."
771  code "haskell" "examine Slot"
772  h2_ "slot machine"
773  p_ "now that you're closer to the slot , you notice a hand-written sign next to it that says :"
774  blockquote_ "slot machine : enter the slot & slide like a coin to a random location"
775  p_ "somebody walks over to you & asks what you're doing ."
776  blockquote_ "hello ! i'm trying to figure out what the deal with this slot thing is ."
777  blockquote_ "no you're not . i saw you over there trying to vandalize my hand-written sign ."
778  blockquote_ "you what ? i didn't even touch the sign ."
779  blockquote_ "then how did all of those purple stains get on it ?"
780  p_ "you glance at the sign again . it does appear more stained than you remember it . you wonder , aloud :"
781  blockquote_ "maybe it's from that pool over there ? whatever gravity well is swirling above the pool might have become volatile ."
782  blockquote_ "that's certainly a possiblity . but it seems much more likely that you hated my handwriting style & wanted to destroy it yourself ."
783  blockquote_ "you serious ? i didn't even think of the handwriting style until now. it was perfectly serviceable ."
784  blockquote_ "oh ."
785  p_ "they gaze into the distance uncomfortably ."
786  p_ "the grinding sound grows louder , & the crimson glow brighter ."
787  p_ $ em_ "shard count : 3"
788  code "haskell" "ask SignPainter . about Sound"
789  p_ "you ask the sign painter if they know where that sound is coming from ."
790  blockquote_ "no ."
791  code "haskell" "ask SignPainter . about CrimsonGlow"
792  p_ "you ask them if they know what the crimson glow is coming from ."
793  blockquote_ "no ."
794  p_ "the sign painter sits on the ground , placing their legs into the slot . they carefully lower the rest of their body into the slot & let go. a few seconds later the sound of them sliding fades away completely ."
795  p_ "it starts to rain . the droplets are purple , & stains your grey dress ."
796  code "haskell" "go East"
797  p_ "you hover back down the cliff face & land on the boardwalk again ."
798  h2_ "the center"
799  p_ "it feels nice to return to the center . that plateau to the west had an unpleasant vibe . the boardwalk continues to the north , south , & east ."
800  code "haskell" "go West"
801  p_ "you look back at the cliff face . a voice in your head says it may be a good idea to return to the slot machine , because it could spit you out where you need to go much faster than hovering there yourself ."
802  p_ "but no . that would be a gamble ."
803  p_ "you don't like leaving things to chance ."
804  code "haskell" "go North"
805  p_ "with your mind made up , you hover northward along the boardwalk ."
806  h2_ "an expanse"
807  p_ "you've reached the end of the boardwalk . this location is so far from the plateau that it's barely visible through the rain . the crimson glow to the north stretches higher into the sky here . it's like the source of the grinding noise is a wall in the distance that wraps around the boundary of b6e's mind ."
808  p_ "there is a swarm of winged , metal centipedes flying over your head ."
809  p_ "the grinding sound is loud enough here to put you on edge ."
810  p_ $ em_ "shard count : 4"
811  code "haskell" "ask Centipede . about Sound"
812  p_ "you call out to the centipedes above you ."
813  blockquote_ "excuse me , would any of you be able to help me answer a quick question ?"
814  p_ "one of them lands in front of you . they are wearing a really cool sweater with a fractal pattern knitted onto it ."
815  blockquote_ "i might be able to help ya ! what's ur question ?"
816  blockquote_ "oh nice ! thank you . do you know what that glass grinding noise in the distance is ?"
817  blockquote_ "ya mean death ?"
818  blockquote_ "what ?"
819  blockquote_ "death . like the thing that happens when ya have a shard count of 11 ? looks like ya have 4 shards . ya might wanna stop thinkin' 'bout the wall !! you'll get less shards that way !"
820  p_ "the other centipedes start gliding to the southeast ."
821  blockquote_ "that's what the shard count is about ? why would thinking about the wall give you more shards ? by the wall you mean that crimson thing in the distance , right ?"
822  blockquote_ "hey kid i'm sorry but i gotta go my friends are leavin' & i don't wanna get left behind but i'm sure someone else can help ya out ! althoughhh a lotta entities might be hesitant ( ior worse ) to talk about the shards . not sure what to tell ya 'bout that ."
823  blockquote_ "ok , well thanks for the info . i'll keep searching then ."
824  blockquote_ "be careful ."
825  p_ "they fly away ."
826  code "haskell" "save"
827  p_ $ em_ "serializing timeline ..."
828  p_ $ em_ "game saved ."
829  p_ $ em_ $ do
830    "enter the code "
831    code_ [class_ "verbatim"] "5nJ0kL3-001"
832    " to restore the game to this point in time ."
833  code "haskell" "pop"