diff options
125 files changed, 1576 insertions, 0 deletions
diff --git a/.gitignore b/.gitignore new file mode 100644 index 0000000..8ee1bf9 --- /dev/null +++ b/.gitignore @@ -0,0 +1 @@ +.stack-work @@ -0,0 +1,16 @@ +Antiquitysort +Copyright (C) 2020 cyfraeviolae.org + +This program is free software: you can redistribute it and/or modify +it under the terms of the GNU Affero General Public License as +published by the Free Software Foundation, either version 3 of the +License, or (at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU Affero General Public License for more details. + +You should have received a copy of the GNU Affero General Public License +along with this program. If not, see <https://www.gnu.org/licenses/>. + diff --git a/README.md b/README.md new file mode 100644 index 0000000..55ee215 --- /dev/null +++ b/README.md @@ -0,0 +1,22 @@ +# Antiquitysort + +- ensure no dupe years in code +- implement versioning +- classical works are too close together... +- better editing and selection of works +- creator +- sorting network? +- prettier errors +- fml maybe do date of consecration +- or maybe notes to indicate what date to consider for each hej if not initial + +- benedictine church of murbach alsace +- saint chapelle +- strasbourg - date unclear +- choir of churcvh at st piertre +- old chancellery la greffe bruges +santa agnese piazza navona +- hagia sophia unclear date +kinkauji - specify +nanzenji +enryaku-jik diff --git a/Setup.hs b/Setup.hs new file mode 100644 index 0000000..9a994af --- /dev/null +++ b/Setup.hs @@ -0,0 +1,2 @@ +import Distribution.Simple +main = defaultMain diff --git a/antiquitysort.cabal b/antiquitysort.cabal new file mode 100644 index 0000000..7a1bfb9 --- /dev/null +++ b/antiquitysort.cabal @@ -0,0 +1,83 @@ +cabal-version: 1.12 + +-- This file has been generated from package.yaml by hpack version 0.34.3. +-- +-- see: https://github.com/sol/hpack + +name: antiquitysort +version: 0.1.0.0 +description: Please see the README on GitHub at <https://github.com/githubuser/antiquitysort#readme> +author: cyfraeviolae +maintainer: cyfraeviolae +copyright: 2020 cyfraeviolae.org +license: AGPL +license-file: LICENSE +build-type: Simple +extra-source-files: + README.md + +library + exposed-modules: + Lib + other-modules: + Paths_antiquitysort + hs-source-dirs: + src + ghc-options: -Wall -fwarn-incomplete-uni-patterns + build-depends: + aeson + , array + , base >=4.7 && <5 + , binary + , bytestring + , containers + , either + , hex-text + , http-api-data + , lucid + , mtl + , random + , safe-exceptions + , servant-lucid + , servant-server + , sort + , split + , string-conversions + , text + , tomland + , wai + , warp + default-language: Haskell2010 + +executable antiquitysort-exe + main-is: Main.hs + other-modules: + Paths_antiquitysort + hs-source-dirs: + app + ghc-options: -threaded -rtsopts -with-rtsopts=-N + build-depends: + aeson + , antiquitysort + , array + , base + , binary + , bytestring + , containers + , either + , hex-text + , http-api-data + , lucid + , mtl + , random + , safe-exceptions + , servant-lucid + , servant-server + , sort + , split + , string-conversions + , text + , tomland + , wai + , warp + default-language: Haskell2010 diff --git a/antiquitysort.service b/antiquitysort.service new file mode 100644 index 0000000..b03cd36 --- /dev/null +++ b/antiquitysort.service @@ -0,0 +1,12 @@ +[Unit] +Description=antiquity +After=network.target + +[Service] +Type=simple +Restart=on-failure +ExecStart=/srv/antiquitysort/antiquitysort-exe +WorkingDirectory=/srv/antiquitysort/ + +[Install] +WantedBy=multi-user.target diff --git a/app/Main.hs b/app/Main.hs new file mode 100644 index 0000000..666dde6 --- /dev/null +++ b/app/Main.hs @@ -0,0 +1,11 @@ +module Main where + +import Lib +import Toml + +main :: IO () +main = do + manifest <- Lib.loadManifest + case manifest of + Left errs -> print $ prettyTomlDecodeErrors errs + Right manifest -> startApp manifest @@ -0,0 +1,6 @@ +#!/usr/bin/env bash +set -euo pipefail +stack install +rsync ~/.local/bin/antiquitysort-exe vps:/srv/antiquitysort/staging +rsync antiquitysort.service vps:/srv/antiquitysort/staging +rsync -az static vps:/srv/antiquitysort/staging diff --git a/hie.yaml b/hie.yaml new file mode 100644 index 0000000..4ef275e --- /dev/null +++ b/hie.yaml @@ -0,0 +1,2 @@ +cradle: + stack: diff --git a/package.yaml b/package.yaml new file mode 100644 index 0000000..74db047 --- /dev/null +++ b/package.yaml @@ -0,0 +1,60 @@ +name: antiquitysort +version: 0.1.0.0 +license: AGPL +author: "cyfraeviolae" +maintainer: "cyfraeviolae" +copyright: "2020 cyfraeviolae.org" + +extra-source-files: +- README.md + +# Metadata used when publishing your package +# synopsis: Short description of your package +# category: Web + +# To avoid duplicated efforts in documentation and dealing with the +# complications of embedding Haddock markup inside cabal files, it is +# common to point users to the README.md file. +description: Please see the README on GitHub at <https://github.com/githubuser/antiquitysort#readme> + +dependencies: +- base >= 4.7 && < 5 +- aeson +- servant-server +- wai +- warp +- containers +- string-conversions +- text +- lucid +- safe-exceptions +- http-api-data +- servant-lucid +- random +- tomland +- mtl +- hex-text +- binary +- either +- bytestring +- array +- split +- sort + +library: + source-dirs: src + ghc-options: + - -Wall + - -fwarn-incomplete-uni-patterns + +executables: + antiquitysort-exe: + main: Main.hs + source-dirs: app + ghc-options: + - -threaded + - -rtsopts + - -with-rtsopts=-N + dependencies: + - base + - antiquitysort diff --git a/scraper.py b/scraper.py new file mode 100755 index 0000000..7f6144b --- /dev/null +++ b/scraper.py @@ -0,0 +1,27 @@ +#!/usr/bin/env python3 + +# yes, html is not a regular language + +import requests, sys +uris = sys.argv[1:] +import re +for uri in uris: + resp = requests.get(uri).text + lines = resp.split('\n') + license = None + author = None + for idx, line in enumerate(lines): + if 'Original file' in line: + uri = re.match(r'.*href="(.*?)".*', line).group(1) + elif 'licensetpl_short' in line: + license = line.rsplit('>')[-1] + elif author is None and 'Author</td' in line: + author = re.match(r'(.*?>)?(.*?)<.*', lines[idx+2]).group(2) + if not uri.startswith('http'): + uri = 'https:' + uri + r = requests.get(uri, allow_redirects=True) + local_filename = uri.split('/')[-1] + open("./static/assets/" + local_filename, 'wb').write(r.content) + print('[[mediums.works.figures]]') + print('file = "' + local_filename + '"') + print(f'byline = "{license}{author}"') diff --git a/src/Lib.hs b/src/Lib.hs new file mode 100644 index 0000000..e3593db --- /dev/null +++ b/src/Lib.hs @@ -0,0 +1,445 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeOperators #-} +{-# LANGUAGE UndecidableInstances #-} + +module Lib ( startApp, loadManifest ) +where + +import qualified Control.Exception as E +import qualified Control.Exception.Safe as CES +import Control.Monad +import Control.Monad.IO.Class +import Control.Monad.State +import qualified Data.Binary as B +import qualified Data.Binary.Get as BG +import Data.Bits +import qualified Data.ByteString.Lazy as BSL +import Data.Either.Combinators +import qualified Data.List as L +import qualified Data.List.Split as DLS +import qualified Data.Map as M +import Data.Sort +import qualified Data.String.Conversions as DSC +import qualified Data.Text as T +import GHC.Generics +import Lucid +import Network.Wai.Handler.Warp +import Servant hiding ((:.)) +import Servant.HTML.Lucid +import qualified System.Random as R +import Text.Hex +import Toml +import Web.HttpApiData + +newtype Manifest = Manifest { mediums :: [Medium] } +data Medium = Medium { tag :: MediumTag + , label :: T.Text + , description :: T.Text + , disabled :: Bool + , works :: [Work] } +data Figure = Figure { file :: T.Text + , byline :: T.Text } +data Work = Work { name :: T.Text + , year :: Integer + , location :: T.Text + , wiki :: T.Text + , figures :: [Figure] } +instance Eq Work where + (==) Work{year=y1} Work{year=y2} = y1 == y2 +instance Ord Work where + compare Work{year=y1} Work{year=y2} = compare y1 y2 +manifestCodec :: Toml.TomlCodec Manifest +manifestCodec = Manifest + <$> Toml.list mediumCodec "mediums" .= mediums +mediumCodec :: Toml.TomlCodec Medium +mediumCodec = Medium + <$> Toml.diwrap (Toml.text "tag") .= tag + <*> Toml.text "label" .= label + <*> Toml.text "description" .= description + <*> Toml.bool "disabled" .= disabled + <*> Toml.list workCodec "works" .= works +workCodec :: Toml.TomlCodec Work +workCodec = Work + <$> Toml.text "name" .= name + <*> Toml.integer "year" .= year + <*> Toml.text "location" .= location + <*> Toml.text "wiki" .= wiki + <*> Toml.list figureCodec "figures" .= figures +figureCodec :: Toml.TomlCodec Figure +figureCodec = Figure + <$> Toml.text "file" .= file + <*> Toml.text "byline" .= byline + +newtype HomeView = HomeView Manifest +data PlayView = GameView [MediumTag] [T.Text] [Period] Level GameState (Work, Work) + | FinalView [MediumTag] [T.Text] [Period] Level [Work] [Work] Integer +newtype MediumTag = MediumTag T.Text deriving (Eq, Show, Ord, ToHttpApiData, FromHttpApiData, ToHtml) +data Period = Ancient | Postclassical | EarlyModern | Modern deriving (Eq, Show, Read, Bounded, Enum) +data Level = Short | Long deriving (Eq, Show, Read, Bounded, Enum) +instance ToHttpApiData Period where + toUrlPiece = tshow +instance FromHttpApiData Period where + parseUrlPiece = parseBoundedUrlPiece +instance ToHttpApiData Level where + toUrlPiece = tshow +instance FromHttpApiData Level where + parseUrlPiece = parseBoundedUrlPiece + +periodElem :: Integer -> [Period] -> Bool +periodElem x = L.any (isIn x) + where isIn y Ancient = y <= 600 + isIn y Postclassical = y >= 400 && y <= 1600 + isIn y EarlyModern = y >= 1400 && y <= 1850 + isIn y Modern = y >= 1750 +data Order = Less | Greater deriving (Eq, Show) +newtype Decisions = Decisions [Order] deriving (Eq, Show) +newtype Version = Version B.Word8 deriving (Eq, Show, FromHttpApiData, Generic, Num) +newtype Seed = Seed B.Word16 deriving (Eq, Show, FromHttpApiData, Generic, Num, R.Random) +-- TODO fml use bitvec pkg +instance B.Binary Decisions where + get = do + c <- fromIntegral <$> B.getWord8 + b <- BG.getByteString (div c 8 + (if 0 == mod c 8 then 0 else 1)) + let res = concatMap (\x -> fmap (\i -> if 0 == shiftR x i .&. 1 then Less else Greater) [0..7]) (BSL.unpack . BSL.fromStrict $ b) + return $ Decisions (take c res) + put (Decisions comps) = + B.putWord8 (fromIntegral (mod (length comps) 256)) + <> + mapM_ B.putWord8 intchunks + where + chunks = DLS.chunksOf 8 comps + convchunk = fmap (\x -> if x == Less then (0 :: Integer) else 1) + intify convd = (fromIntegral $ Prelude.sum $ (\(x, i) -> x * (2 ^ i)) <$> zip convd [(0 :: Integer)..]) :: B.Word8 + intchunks = fmap (intify .convchunk) chunks +instance B.Binary Version +instance B.Binary Seed +data GameState = GameState Version Seed Decisions deriving (Eq, Show) +instance B.Binary GameState where + get = GameState <$> B.get <*> B.get <*> B.get + put (GameState version seed decisions) = B.put version >> B.put seed >> B.put decisions + +instance ToHttpApiData GameState where + toUrlPiece = encodeHex . BSL.toStrict . B.encode +instance FromHttpApiData GameState where + parseUrlPiece s = do + b <- maybeToRight "failed to decode state" (decodeHex s) + case B.decodeOrFail (BSL.fromStrict b) of + Left (_, _, err) -> Left (T.pack err) + Right (_, _, x) -> Right x + +type HomeAPI = Get '[HTML] HomeView +type PlayAPI = "play" + :> QueryParams "m" MediumTag + :> QueryParams "p" Period + :> QueryParam "l" Level + :> QueryParam "s" GameState + :> Get '[HTML] PlayView + +type API = HomeAPI :<|> PlayAPI :<|> "static" :> Raw + +startApp :: Manifest -> IO () +startApp manifest = run 8090 (app manifest) + +app :: Manifest -> Application +app manifest = serve api $ hoistServer api handleErrors (server manifest) + +handleErrors :: Handler a -> Handler a +handleErrors f = + CES.catches + f + [ CES.Handler (loggify handleAppException), + CES.Handler (loggify handleArbitraryException) + ] + +api :: Proxy API +api = Proxy + +server :: Manifest -> Server API +server manifest = + handleHome manifest + :<|> handlePlay manifest + :<|> serveDirectoryWebApp "static/" + +redirectTo :: T.Text -> Handler a +redirectTo uri = throwError err302 {errHeaders = [("Location", DSC.cs uri)]} + +------------------------------ + +loadManifest :: IO (Either [TomlDecodeError] Manifest) +loadManifest = Toml.decodeFileEither manifestCodec "static/manifest.toml" + +data AppException = NotEnoughWorks | NeedAMedium | NeedAPeriod | NeedLevel deriving (Show) + +instance E.Exception AppException + +loggify :: E.Exception b => (b -> Handler a) -> b -> Handler a +loggify f ex = do + liftIO $ print ex + f ex + +handleArbitraryException :: E.SomeException -> Handler a +handleArbitraryException _ = throwError err500 {errBody = "500: An unexpected error occurred."} + +handleAppException :: AppException -> Handler a +handleAppException NotEnoughWorks = + throwError err400 {errBody = "400: Sorry, not enough works match these options. Please choose more folios or periods."} +handleAppException NeedAMedium = + throwError err400 {errBody = "400: Need at least one folio."} +handleAppException NeedAPeriod = + throwError err400 {errBody = "400: Need at least one period."} +handleAppException NeedLevel = + throwError err400 {errBody = "400: Need a duration."} + +handleHome :: Manifest -> Handler HomeView +handleHome manifest = return $ HomeView manifest + +currentVersion :: Version +currentVersion = Version 1 + +handlePlay :: Manifest -> [MediumTag] -> [Period] -> Maybe Level -> Maybe GameState -> Handler PlayView +handlePlay _ [] _ _ _ = E.throw NeedAMedium +handlePlay _ _ [] _ _ = E.throw NeedAPeriod +handlePlay _ _ _ Nothing _ = E.throw NeedLevel +handlePlay _ mediumTags periods (Just level) Nothing = do + seed <- liftIO R.randomIO + redirectTo $ playURI mediumTags periods level (Just (GameState currentVersion seed (Decisions []))) +handlePlay Manifest{mediums} mediumTags periods (Just level) + (Just gameState@(GameState _ (Seed seed) (Decisions comparisons))) = do + let mediums' = filter ((`elem` mediumTags) . tag) mediums + labels = fmap label mediums' + works' = concatMap works mediums' + works'' = filter ((`periodElem` periods) . year) works' + liftIO $ when (length works'' < levelLength level) $ E.throw NotEnoughWorks + let rng = R.mkStdGen (fromIntegral seed) + (works''', _) = fisherYates rng works'' + works'''' = take (levelLength level) works''' + (userWorks, nextPair, misses) = antiquitySort works'''' comparisons + case nextPair of + Just workPair -> return $ GameView mediumTags labels periods level gameState workPair + Nothing -> return $ FinalView mediumTags labels periods level userWorks (sortOn year works'''') misses + +levelLength :: Level -> Int +levelLength Short = 6 +levelLength Long = 10 + +-- from Haskell wiki +fisherYatesStep :: R.RandomGen g => (M.Map Int a, g) -> (Int, a) -> (M.Map Int a, g) +fisherYatesStep (m, gen) (i, x) = ((M.insert j x . M.insert i (m M.! j)) m, gen') + where + (j, gen') = R.randomR (0, i) gen + +-- from Haskell wiki +fisherYates :: R.RandomGen g => g -> [a] -> ([a], g) +fisherYates gen [] = ([], gen) +fisherYates gen l = + toElems $ foldl fisherYatesStep (initial (head l) gen) (numerate (tail l)) + where + toElems (x, y) = (M.elems x, y) + numerate = zip [1..] + initial x g = (M.singleton 0 x, g) + +antiquitySort :: Ord a => [a] -> [Order] -> ([a], Maybe (a, a), Integer) +antiquitySort elements orders = + let ((sortedElements, misses), (_, next)) = runState (antiquitySort' elements) (orders, Nothing) + in (sortedElements, next, misses) + where + antiquitySort' :: Ord a => [a] -> State ([Order], Maybe (a, a)) ([a], Integer) + antiquitySort' [] = return ([], 0) + antiquitySort' [x] = return ([x], 0) + antiquitySort' xs = do + let (ys, zs) = splitAt (div (length xs) 2) xs + (sortedYs, missesYs) <- antiquitySort' ys + (sortedZs, missesZs) <- antiquitySort' zs + (sortedXs, missesCombine) <- combine sortedYs sortedZs + return (sortedXs, missesYs + missesZs + missesCombine) + combine :: Ord a => [a] -> [a] -> State ([Order], Maybe (a, a)) ([a], Integer) + combine [] ys = return (ys, 0) + combine xs [] = return (xs, 0) + combine allXs@(x:xs) allYs@(y:ys) = consumeOrder >>= \case + Nothing -> do + get >>= \case + (cs, Nothing) -> put (cs, Just (x, y)) + _ -> return () + return (allXs ++ allYs, 0) + Just Less -> do + (combined, misses) <- combine xs allYs + return (x:combined, misses + (if x < y then 0 else 1)) + Just Greater -> do + (combined, misses) <- combine allXs ys + return (y:combined, misses + (if x > y then 0 else 1)) + consumeOrder :: State ([Order], Maybe (a, a)) (Maybe Order) + consumeOrder = get >>= \case + ([], _) -> return Nothing + (x:xs, next) -> do + put (xs, next) + return (Just x) + +------------------------------- + +homeURI :: T.Text +homeURI = "/" <> toUrlPiece (safeLink api (Proxy :: Proxy HomeAPI) :: Link) + +playURI :: [MediumTag] -> [Period] -> Level -> Maybe GameState -> T.Text +playURI mediumTags periods level gameState = "/" <> toUrlPiece (safeLink api (Proxy :: Proxy PlayAPI) mediumTags periods (Just level) gameState :: Link) + +------------------------------- + +gameCrumbs :: Monad m => [MediumTag] -> [T.Text] -> [Period] -> Level -> [HtmlT m ()] +gameCrumbs _ labels periods level = [ + span_ $ toHtml $ T.intercalate ", " labels + , span_ $ toHtml $ T.intercalate ", " (fmap tshow periods) + , span_ $ toHtml . tshow $ level ] + +instance ToHtml HomeView where + toHtml (HomeView (Manifest mediums)) = + pageTemplate + [a_ [href_ "https://git.cyfraeviolae.org/antiquitysort"] "source code"] + homeBody + where + homeBody = div_ [class_ "narrow"] $ do + p_ $ toHtmlRaw $ T.pack "The spectral sorcerer Roseacrucis has cast his nefarious randomizing algorithms upon the Library’s chronicles. Your mission is to restore the well‐ordering of our cultural histories." + form_ [method_ "get", action_ "/play"] $ do + fieldset_ $ do + legend_ "Folios" + forM_ mediums $ \Medium{tag=(MediumTag tagm),label,description,disabled} -> div_ $ do + input_ $ [type_ "checkbox", name_ "m", value_ tagm, id_ tagm] ++ + [checked_ | tagm == "ReligiousArchitecture"] ++ + [disabled_ "1" | disabled] + label_ [for_ tagm] $ do + span_ $ strong_ $ toHtml label <> ". " + if disabled + then span_ "Coming soon." + else span_ $ toHtmlRaw description + fieldset_ $ do + legend_ "Periods" + div_ $ do + input_ [type_ "checkbox", name_ "p", value_ "Ancient", id_ "Ancient", checked_] + label_ [for_ "Ancient"] $ do + span_ $ strong_ "Ancient " + span_ $ toHtmlRaw $ T.pack "(3000 BCE—600 CE)" + div_ $ do + input_ [type_ "checkbox", name_ "p", value_ "Postclassical", id_ "Postclassical"] + label_ [for_ "Postclassical"] $ do + span_ $ strong_ "Postclassical " + span_ $ toHtmlRaw $ T.pack "(400 CE—1600 CE)" + div_ $ do + input_ [type_ "checkbox", name_ "p", value_ "EarlyModern", id_ "EarlyModern"] + label_ [for_ "EarlyModern"] $ do + span_ $ strong_ "Early modern " + span_ $ toHtmlRaw $ T.pack "(1400 CE—1850 CE)" + div_ $ do + input_ [type_ "checkbox", name_ "p", value_ "Modern", id_ "Modern"] + label_ [for_ "Modern"] $ do + span_ $ strong_ "Modern " + span_ $ toHtmlRaw $ T.pack "(1750 CE—)" + fieldset_ $ do + legend_ "Duration" + div_ $ do + input_ [type_ "radio", name_ "l", value_ "Short", id_ "Short", checked_] + label_ [for_ "Short"] $ do + span_ $ strong_ "Short " + span_ "(6 works, less than 11 questions)" + div_ $ do + input_ [type_ "radio", name_ "l", value_ "Long", id_ "Long"] + label_ [for_ "Long"] $ do + span_ $ strong_ "Long " + span_ "(10 works, less than 25 questions)" + button_ [type_ "submit"] "Start" + toHtmlRaw = toHtml + +feedbackPerfect :: Integer -> T.Text +feedbackPerfect _ = "Hurrah! The chronicles are once again in perfect order. You have foiled not only the perfidious Roseacrucis, but even the divine disorder induced by the Arrow of Time itself. The Library moves to induct you into the illustrious Order of the Temporal Modality. But our revelry must be short-lived, for Roseacrucis may one day return…" +feedbackMiddling :: Integer -> T.Text +feedbackMiddling misses = "The Library congratulates your worthy efforts, for only " <> (if misses == 1 then "one question was" else tshow misses <> " questions were") <> " answered incorrectly. With further training, you may one day defeat Roseacrucis." +feedbackPoor :: Integer -> T.Text +feedbackPoor misses = "The Library regrets to inform you that due to the " <> (if misses == 1 then "one question" else tshow misses <> " questions") <> " that you answered incorrectly, we have made absolutely no progress in emending the enigma of entropy engendered by Roseacrucis." + +feedback :: Level -> Integer -> T.Text +feedback _ 0 = feedbackPerfect 0 +feedback level misses = + if (level == Short && misses <= 4) || (level == Long && misses <= 8) + then feedbackMiddling misses + else feedbackPoor misses + +showCard :: Monad m => Work -> HtmlT m () +showCard Work{name,year,wiki} = do + a_ [href_ wiki] (toHtml name) + span_ $ toHtml $ " (" <> tshow (abs year) <> " " <> (if year < 0 then "BCE)" else "CE)") + +renderWork :: Monad m => Work -> HtmlT m () -> HtmlT m () +renderWork Work{figures} header = div_ [class_ "work"] $ do + div_ $ strong_ header + div_ [class_ "subwork"] $ mapM_ renderFigure figures +renderFigure :: Monad m => Figure -> HtmlT m () +renderFigure Figure{file,byline} = figure_ $ do + img_ [src_ ("/static/assets/" <> file)] + figcaption_ $ toHtml byline + +instance ToHtml PlayView where + toHtml (FinalView mediumTags labels periods level userWorks sortedWorks misses) = + pageTemplate (gameCrumbs mediumTags labels periods level) body + where + body = do + div_ [class_ "row"] $ div_ [class_ "narrow"] $ do + p_ . toHtmlRaw $ feedback level misses + p_ $ do + a_ [href_ (playURI mediumTags periods level Nothing)] "Retry the current game" + span_ ", or " + a_ [href_ homeURI] "choose different folios and periods" + span_ "." + div_ [class_ "row"] $ table_ $ do + tr_ $ th_ "Your ordering" <> th_ "Correct ordering" + mapM_ (\(userWork, sortedWork) -> tr_ $ + td_ (showCard userWork) <> td_ (showCard sortedWork)) + (zip userWorks sortedWorks) + div_ [class_ "row"] $ div_ [class_ ""] $ mapM_ (\work -> do + renderWork work $ p_ $ showCard work <> p_ (toHtml $ location work) + br_ []) sortedWorks + toHtml (GameView mediumTags labels periods level (GameState v s (Decisions comps)) (work1, work2)) = + pageTemplate (gameCrumbs mediumTags labels periods level) body + where + body = do + div_ [class_ "row"] $ p_ $ do + strong_ . toHtml $ "Question " <> tshow (length comps + 1) <> ". " + span_ "Select the work that was created first. Dates for ancient works are approximate and reflect when construction began." + div_ [class_ "row"] $ do + renderWork work1 (a_ [href_ (mkURI Less)] "Work A was created first.") + hr_ [] + renderWork work2 (a_ [href_ (mkURI Greater)] "Work B was created first.") + mkURI nxt = playURI mediumTags periods level (Just (GameState v s (Decisions (comps ++ [nxt])))) + toHtmlRaw = toHtml + +pageTemplate :: Monad m => [HtmlT m ()] -> HtmlT m () -> HtmlT m () +pageTemplate crumbs body = doctypehtml_ $ do + head_ $ do + title_ "Antiquitysort" + meta_ [charset_ "utf-8"] + meta_ [name_ "viewport", content_ "width=device-width, initial-scale=1.0"] + link_ [rel_ "shortcut icon", type_ "image/x-icon", href_ "/static/favicon.ico"] + link_ [rel_ "stylesheet", type_ "text/css", href_ "/static/style.css"] + body_ $ + div_ [class_ "container"] $ do + div_ [class_ "row navbar"] $ + sequence_ $ + L.intersperse + (span_ [class_ "sep"] (toHtmlRaw (T.pack " · "))) + (crumb : crumbs) + body + where + crumb = do + a_ [href_ homeURI, class_ "title"] (strong_ "Antiquitysort") + span_ "@" + a_ [href_ "https://cyfraeviolae.org", class_ "title"] "cyfraeviolae" + +tshow :: Show a => a -> T.Text +tshow = T.pack . show diff --git a/stack.yaml b/stack.yaml new file mode 100644 index 0000000..ebd89e8 --- /dev/null +++ b/stack.yaml @@ -0,0 +1,67 @@ +# This file was automatically generated by 'stack init' +# +# Some commonly used options have been documented as comments in this file. +# For advanced use and comprehensive documentation of the format, please see: +# https://docs.haskellstack.org/en/stable/yaml_configuration/ + +# Resolver to choose a 'specific' stackage snapshot or a compiler version. +# A snapshot resolver dictates the compiler version and the set of packages +# to be used for project dependencies. For example: +# +# resolver: lts-3.5 +# resolver: nightly-2015-09-21 +# resolver: ghc-7.10.2 +# +# The location of a snapshot can be provided as a file or url. Stack assumes +# a snapshot provided as a file might change, whereas a url resource does not. +# +# resolver: ./custom-snapshot.yaml +# resolver: https://example.com/snapshots/2018-01-01.yaml +resolver: + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/16/27.yaml + +# User packages to be built. +# Various formats can be used as shown in the example below. +# +# packages: +# - some-directory +# - https://example.com/foo/bar/baz-0.0.2.tar.gz +# subdirs: +# - auto-update +# - wai +packages: +- . +# Dependency packages to be pulled from upstream that are not in the resolver. +# These entries can reference officially published versions as well as +# forks / in-progress versions pinned to a git hash. For example: +# +extra-deps: + - ghc-exactprint-0.6.3.3@sha256:384e1066c192ed60dc12443b7aca75a4a4adcc47f829336c21ed007596fe683f,9446 + - hex-text-0.1.0.2 + - base16-bytestring-1.0.1.0 + +# extra-deps: [] + +# Override default flag values for local packages and extra-deps +# flags: {} + +# Extra package databases containing global packages +# extra-package-dbs: [] + +# Control whether we use the GHC we find on the path +# system-ghc: true +# +# Require a specific version of stack, using version ranges +# require-stack-version: -any # Default +# require-stack-version: ">=2.5" +# +# Override the architecture used by stack, especially useful on Windows +# arch: i386 +# arch: x86_64 +# +# Extra directories used by stack for building +# extra-include-dirs: [/path/to/dir] +# extra-lib-dirs: [/path/to/dir] +# +# Allow a newer minor version of GHC than the snapshot specifies +# compiler-check: newer-minor diff --git a/stack.yaml.lock b/stack.yaml.lock new file mode 100644 index 0000000..e24f83d --- /dev/null +++ b/stack.yaml.lock @@ -0,0 +1,34 @@ +# This file was autogenerated by Stack. +# You should not edit this file by hand. +# For more information, please see the documentation at: +# https://docs.haskellstack.org/en/stable/lock_files + +packages: +- completed: + hackage: ghc-exactprint-0.6.3.3@sha256:384e1066c192ed60dc12443b7aca75a4a4adcc47f829336c21ed007596fe683f,9446 + pantry-tree: + size: 86248 + sha256: c43b6e600634f5d5df2feb69e27e745fff25fe60503a30d3e5c86428882b686f + original: + hackage: ghc-exactprint-0.6.3.3@sha256:384e1066c192ed60dc12443b7aca75a4a4adcc47f829336c21ed007596fe683f,9446 +- completed: + hackage: hex-text-0.1.0.2@sha256:154df2b81c1dd38b055fa6a90cb6964f60c5cf4a0ba633ea929d8a79af89519a,1301 + pantry-tree: + size: 368 + sha256: 9271e478d8bdd05760ae5ed86f72f28065e3a942019c79b5a69dc604a4b0e1a8 + original: + hackage: hex-text-0.1.0.2 +- completed: + hackage: base16-bytestring-1.0.1.0@sha256:33b9d57afa334d06485033e930c6b13fc760baf88fd8f715ae2f9a4b46e19a54,2641 + pantry-tree: + size: 595 + sha256: 24661ef9b1089d468227300f8ceb89194b5cce68b9f6ed8109b01f63c07f54e3 + original: + hackage: base16-bytestring-1.0.1.0 +snapshots: +- completed: + size: 533252 + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/16/27.yaml + sha256: c2aaae52beeacf6a5727c1010f50e89d03869abfab6d2c2658ade9da8ed50c73 + original: + url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/16/27.yaml diff --git a/static/EBGaramond-Italic-VariableFont_wght.ttf b/static/EBGaramond-Italic-VariableFont_wght.ttf Binary files differnew file mode 100644 index 0000000..fa31b71 --- /dev/null +++ b/static/EBGaramond-Italic-VariableFont_wght.ttf diff --git a/static/EBGaramond-VariableFont_wght.ttf b/static/EBGaramond-VariableFont_wght.ttf Binary files differnew file mode 100644 index 0000000..123d5dd --- /dev/null +++ b/static/EBGaramond-VariableFont_wght.ttf diff --git a/static/assets/070526_Stift_Melk_02.jpg b/static/assets/070526_Stift_Melk_02.jpg Binary files differnew file mode 100644 index 0000000..f3c2882 --- /dev/null +++ b/static/assets/070526_Stift_Melk_02.jpg diff --git a/static/assets/0_Amiens_-_Cathédrale_Notre-Dame_(1).JPG b/static/assets/0_Amiens_-_Cathédrale_Notre-Dame_(1).JPG Binary files differnew file mode 100644 index 0000000..f986b1b --- /dev/null +++ b/static/assets/0_Amiens_-_Cathédrale_Notre-Dame_(1).JPG diff --git a/static/assets/11_Temple_of_Heaven.jpg b/static/assets/11_Temple_of_Heaven.jpg Binary files differnew file mode 100644 index 0000000..e4f6ea2 --- /dev/null +++ b/static/assets/11_Temple_of_Heaven.jpg diff --git a/static/assets/1280px-Athen_Erechtheion_BW_2017-10-09_13-58-34.jpg b/static/assets/1280px-Athen_Erechtheion_BW_2017-10-09_13-58-34.jpg Binary files differnew file mode 100644 index 0000000..9ee3a23 --- /dev/null +++ b/static/assets/1280px-Athen_Erechtheion_BW_2017-10-09_13-58-34.jpg diff --git a/static/assets/1280px-Dome_of_Pantheon_Rome.JPG b/static/assets/1280px-Dome_of_Pantheon_Rome.JPG Binary files differnew file mode 100644 index 0000000..84767b1 --- /dev/null +++ b/static/assets/1280px-Dome_of_Pantheon_Rome.JPG diff --git a/static/assets/1280px-Erechtheum_Acropolis_Athens.jpg b/static/assets/1280px-Erechtheum_Acropolis_Athens.jpg Binary files differnew file mode 100644 index 0000000..0cf3a55 --- /dev/null +++ b/static/assets/1280px-Erechtheum_Acropolis_Athens.jpg diff --git a/static/assets/1280px-Pantheon_Rom_1_cropped.jpg b/static/assets/1280px-Pantheon_Rom_1_cropped.jpg Binary files differnew file mode 100644 index 0000000..4641008 --- /dev/null +++ b/static/assets/1280px-Pantheon_Rom_1_cropped.jpg diff --git a/static/assets/1280px-Parthenon,_Acropolis,_Athens,_Greece.jpg b/static/assets/1280px-Parthenon,_Acropolis,_Athens,_Greece.jpg Binary files differnew file mode 100644 index 0000000..6778e94 --- /dev/null +++ b/static/assets/1280px-Parthenon,_Acropolis,_Athens,_Greece.jpg diff --git a/static/assets/1280px-Parthenon_from_west.jpg b/static/assets/1280px-Parthenon_from_west.jpg Binary files differnew file mode 100644 index 0000000..d8900f8 --- /dev/null +++ b/static/assets/1280px-Parthenon_from_west.jpg diff --git a/static/assets/1280px-Temple_of_Hephaestus_in_Athens_20180221-1.jpg b/static/assets/1280px-Temple_of_Hephaestus_in_Athens_20180221-1.jpg Binary files differnew file mode 100644 index 0000000..adf09b9 --- /dev/null +++ b/static/assets/1280px-Temple_of_Hephaestus_in_Athens_20180221-1.jpg diff --git a/static/assets/1280px-Temple_of_Hephaestus_in_Athens_20180221-2.jpg b/static/assets/1280px-Temple_of_Hephaestus_in_Athens_20180221-2.jpg Binary files differnew file mode 100644 index 0000000..449317b --- /dev/null +++ b/static/assets/1280px-Temple_of_Hephaestus_in_Athens_20180221-2.jpg diff --git a/static/assets/12th-century_first_Nandi_facing_Shiva_shrine_at_Shaivism_Hindu_temple_Hoysaleswara_arts_Halebidu_Karnataka_India_2.jpg b/static/assets/12th-century_first_Nandi_facing_Shiva_shrine_at_Shaivism_Hindu_temple_Hoysaleswara_arts_Halebidu_Karnataka_India_2.jpg Binary files differnew file mode 100644 index 0000000..8838f42 --- /dev/null +++ b/static/assets/12th-century_first_Nandi_facing_Shiva_shrine_at_Shaivism_Hindu_temple_Hoysaleswara_arts_Halebidu_Karnataka_India_2.jpg diff --git a/static/assets/2012_ravenna_133.jpg b/static/assets/2012_ravenna_133.jpg Binary files differnew file mode 100644 index 0000000..d18714b --- /dev/null +++ b/static/assets/2012_ravenna_133.jpg diff --git a/static/assets/3456px-Nave_of_Basilica_of_Sant'Apollinare_in_Classe,_Ravenna,_Italy.JPG b/static/assets/3456px-Nave_of_Basilica_of_Sant'Apollinare_in_Classe,_Ravenna,_Italy.JPG Binary files differnew file mode 100644 index 0000000..5aa4ef0 --- /dev/null +++ b/static/assets/3456px-Nave_of_Basilica_of_Sant'Apollinare_in_Classe,_Ravenna,_Italy.JPG diff --git a/static/assets/AachenCathedralMainPortalHDR.jpg b/static/assets/AachenCathedralMainPortalHDR.jpg Binary files differnew file mode 100644 index 0000000..9082e8c --- /dev/null +++ b/static/assets/AachenCathedralMainPortalHDR.jpg diff --git a/static/assets/Aachen_Germany_Imperial-Cathedral-01.jpg b/static/assets/Aachen_Germany_Imperial-Cathedral-01.jpg Binary files differnew file mode 100644 index 0000000..8b23768 --- /dev/null +++ b/static/assets/Aachen_Germany_Imperial-Cathedral-01.jpg diff --git a/static/assets/Aachener_Dom_BW_2016-07-09_16-20-40.jpg b/static/assets/Aachener_Dom_BW_2016-07-09_16-20-40.jpg Binary files differnew file mode 100644 index 0000000..d64ec82 --- /dev/null +++ b/static/assets/Aachener_Dom_BW_2016-07-09_16-20-40.jpg diff --git a/static/assets/Abbatiale_Sainte_Trophime_d'Eschau_(1).jpg b/static/assets/Abbatiale_Sainte_Trophime_d'Eschau_(1).jpg Binary files differnew file mode 100644 index 0000000..be4bc12 --- /dev/null +++ b/static/assets/Abbatiale_Sainte_Trophime_d'Eschau_(1).jpg diff --git a/static/assets/Amiens_Cathedral_choir_Wikimedia_Commons.jpg b/static/assets/Amiens_Cathedral_choir_Wikimedia_Commons.jpg Binary files differnew file mode 100644 index 0000000..a6b821b --- /dev/null +++ b/static/assets/Amiens_Cathedral_choir_Wikimedia_Commons.jpg diff --git a/static/assets/Ancient_ziggurat_at_Ali_Air_Base_Iraq_2005.jpg b/static/assets/Ancient_ziggurat_at_Ali_Air_Base_Iraq_2005.jpg Binary files differnew file mode 100644 index 0000000..761a21c --- /dev/null +++ b/static/assets/Ancient_ziggurat_at_Ali_Air_Base_Iraq_2005.jpg diff --git a/static/assets/Angkor-Wat-from-the-air.JPG b/static/assets/Angkor-Wat-from-the-air.JPG Binary files differnew file mode 100644 index 0000000..c174630 --- /dev/null +++ b/static/assets/Angkor-Wat-from-the-air.JPG diff --git a/static/assets/Angkor_Vat_(6931599619).jpg b/static/assets/Angkor_Vat_(6931599619).jpg Binary files differnew file mode 100644 index 0000000..7501f2e --- /dev/null +++ b/static/assets/Angkor_Vat_(6931599619).jpg diff --git a/static/assets/Attica_06-13_Athens_25_Olympian_Zeus_Temple.jpg b/static/assets/Attica_06-13_Athens_25_Olympian_Zeus_Temple.jpg Binary files differnew file mode 100644 index 0000000..d3695d4 --- /dev/null +++ b/static/assets/Attica_06-13_Athens_25_Olympian_Zeus_Temple.jpg diff --git a/static/assets/Berlin_-_Pergamonmuseum_-_Altar_01.jpg b/static/assets/Berlin_-_Pergamonmuseum_-_Altar_01.jpg Binary files differnew file mode 100644 index 0000000..6d338bd --- /dev/null +++ b/static/assets/Berlin_-_Pergamonmuseum_-_Altar_01.jpg diff --git a/static/assets/Cambridge_King's_College_Chapel.jpg b/static/assets/Cambridge_King's_College_Chapel.jpg Binary files differnew file mode 100644 index 0000000..e3230a3 --- /dev/null +++ b/static/assets/Cambridge_King's_College_Chapel.jpg diff --git a/static/assets/Catedral_de_Salzburgo,_Salzburgo,_Austria,_2019-05-19,_DD_08.jpg b/static/assets/Catedral_de_Salzburgo,_Salzburgo,_Austria,_2019-05-19,_DD_08.jpg Binary files differnew file mode 100644 index 0000000..5f4b086 --- /dev/null +++ b/static/assets/Catedral_de_Salzburgo,_Salzburgo,_Austria,_2019-05-19,_DD_08.jpg diff --git a/static/assets/Cathedral_of_Our_Lady_of_Angels,_Los_Angeles.JPG b/static/assets/Cathedral_of_Our_Lady_of_Angels,_Los_Angeles.JPG Binary files differnew file mode 100644 index 0000000..cbc81a7 --- /dev/null +++ b/static/assets/Cathedral_of_Our_Lady_of_Angels,_Los_Angeles.JPG diff --git a/static/assets/Cathédrale_Notre-Dame_de_Paris,_3_June_2010.jpg b/static/assets/Cathédrale_Notre-Dame_de_Paris,_3_June_2010.jpg Binary files differnew file mode 100644 index 0000000..20b8dae --- /dev/null +++ b/static/assets/Cathédrale_Notre-Dame_de_Paris,_3_June_2010.jpg diff --git a/static/assets/Cathédrale_Notre-Dame_de_Paris_-_15.jpg b/static/assets/Cathédrale_Notre-Dame_de_Paris_-_15.jpg Binary files differnew file mode 100644 index 0000000..9fcdf6a --- /dev/null +++ b/static/assets/Cathédrale_Notre-Dame_de_Paris_-_15.jpg diff --git a/static/assets/Charminar-Pride_of_Hyderabad.jpg b/static/assets/Charminar-Pride_of_Hyderabad.jpg Binary files differnew file mode 100644 index 0000000..e42ea72 --- /dev/null +++ b/static/assets/Charminar-Pride_of_Hyderabad.jpg diff --git a/static/assets/Cherry_blossom_at_the_rock_garden_of_Ryōan-ji_Temple_in_Kyoto,_Japan.jpg b/static/assets/Cherry_blossom_at_the_rock_garden_of_Ryōan-ji_Temple_in_Kyoto,_Japan.jpg Binary files differnew file mode 100644 index 0000000..dacff89 --- /dev/null +++ b/static/assets/Cherry_blossom_at_the_rock_garden_of_Ryōan-ji_Temple_in_Kyoto,_Japan.jpg diff --git a/static/assets/Chichen_Itza_(3326547826).jpg b/static/assets/Chichen_Itza_(3326547826).jpg Binary files differnew file mode 100644 index 0000000..76edab2 --- /dev/null +++ b/static/assets/Chichen_Itza_(3326547826).jpg diff --git a/static/assets/Chiesa_del_Gesù_September_2015-1a.jpg b/static/assets/Chiesa_del_Gesù_September_2015-1a.jpg Binary files differnew file mode 100644 index 0000000..ade3e6f --- /dev/null +++ b/static/assets/Chiesa_del_Gesù_September_2015-1a.jpg diff --git a/static/assets/Chinese-style_minaret_of_the_Great_Mosque.jpg b/static/assets/Chinese-style_minaret_of_the_Great_Mosque.jpg Binary files differnew file mode 100644 index 0000000..c06836a --- /dev/null +++ b/static/assets/Chinese-style_minaret_of_the_Great_Mosque.jpg diff --git a/static/assets/Church_of_the_Gesù,_Rome.jpg b/static/assets/Church_of_the_Gesù,_Rome.jpg Binary files differnew file mode 100644 index 0000000..a1e39c3 --- /dev/null +++ b/static/assets/Church_of_the_Gesù,_Rome.jpg diff --git a/static/assets/Czestochowa-bazylika.jpg b/static/assets/Czestochowa-bazylika.jpg Binary files differnew file mode 100644 index 0000000..1544de1 --- /dev/null +++ b/static/assets/Czestochowa-bazylika.jpg diff --git a/static/assets/Częstochowa_klasztor_Jasna_Góra-2162.jpg b/static/assets/Częstochowa_klasztor_Jasna_Góra-2162.jpg Binary files differnew file mode 100644 index 0000000..046c97b --- /dev/null +++ b/static/assets/Częstochowa_klasztor_Jasna_Góra-2162.jpg diff --git a/static/assets/Darbar_Sahib_interior_26_September_2018.jpg b/static/assets/Darbar_Sahib_interior_26_September_2018.jpg Binary files differnew file mode 100644 index 0000000..25f51ec --- /dev/null +++ b/static/assets/Darbar_Sahib_interior_26_September_2018.jpg diff --git a/static/assets/Dawn_Charles_V_Palace_Alhambra_Granada_Andalusia_Spain.jpg b/static/assets/Dawn_Charles_V_Palace_Alhambra_Granada_Andalusia_Spain.jpg Binary files differnew file mode 100644 index 0000000..abb7bab --- /dev/null +++ b/static/assets/Dawn_Charles_V_Palace_Alhambra_Granada_Andalusia_Spain.jpg diff --git a/static/assets/Deogarh01.jpg b/static/assets/Deogarh01.jpg Binary files differnew file mode 100644 index 0000000..a2fa634 --- /dev/null +++ b/static/assets/Deogarh01.jpg diff --git a/static/assets/Door_Desavatara_Deogarh.jpg b/static/assets/Door_Desavatara_Deogarh.jpg Binary files differnew file mode 100644 index 0000000..0a3216a --- /dev/null +++ b/static/assets/Door_Desavatara_Deogarh.jpg diff --git a/static/assets/Doura_Europos_synagogue_courtyard.jpg b/static/assets/Doura_Europos_synagogue_courtyard.jpg Binary files differnew file mode 100644 index 0000000..925519a --- /dev/null +++ b/static/assets/Doura_Europos_synagogue_courtyard.jpg diff --git a/static/assets/Duomo_Firenze_Apr_2008.jpg b/static/assets/Duomo_Firenze_Apr_2008.jpg Binary files differnew file mode 100644 index 0000000..28fac5a --- /dev/null +++ b/static/assets/Duomo_Firenze_Apr_2008.jpg diff --git a/static/assets/Durham_Cathedral._Interior.jpg b/static/assets/Durham_Cathedral._Interior.jpg Binary files differnew file mode 100644 index 0000000..265061e --- /dev/null +++ b/static/assets/Durham_Cathedral._Interior.jpg diff --git a/static/assets/Durham_MMB_02_Cathedral.jpg b/static/assets/Durham_MMB_02_Cathedral.jpg Binary files differnew file mode 100644 index 0000000..19fda9d --- /dev/null +++ b/static/assets/Durham_MMB_02_Cathedral.jpg diff --git a/static/assets/EarlsBartonChurch.JPG b/static/assets/EarlsBartonChurch.JPG Binary files differnew file mode 100644 index 0000000..540d6fb --- /dev/null +++ b/static/assets/EarlsBartonChurch.JPG diff --git a/static/assets/East_Gateway_-_Stupa_1_-_Sanchi_Hill_2013-02-21_4398.JPG b/static/assets/East_Gateway_-_Stupa_1_-_Sanchi_Hill_2013-02-21_4398.JPG Binary files differnew file mode 100644 index 0000000..6ebf8ed --- /dev/null +++ b/static/assets/East_Gateway_-_Stupa_1_-_Sanchi_Hill_2013-02-21_4398.JPG diff --git a/static/assets/Eglise_Saint-Trophime,_Eschau_4.JPG b/static/assets/Eglise_Saint-Trophime,_Eschau_4.JPG Binary files differnew file mode 100644 index 0000000..cf590e3 --- /dev/null +++ b/static/assets/Eglise_Saint-Trophime,_Eschau_4.JPG diff --git a/static/assets/Exeter-28Ap11-wyrdlight.jpg b/static/assets/Exeter-28Ap11-wyrdlight.jpg Binary files differnew file mode 100644 index 0000000..41700c9 --- /dev/null +++ b/static/assets/Exeter-28Ap11-wyrdlight.jpg diff --git a/static/assets/File:Basilica_of_San_Vitale,_Ravenna,_Italy.jpg b/static/assets/File:Basilica_of_San_Vitale,_Ravenna,_Italy.jpg Binary files differnew file mode 100644 index 0000000..6cff107 --- /dev/null +++ b/static/assets/File:Basilica_of_San_Vitale,_Ravenna,_Italy.jpg diff --git a/static/assets/Giant_Wild_Goose_Pagoda.jpg b/static/assets/Giant_Wild_Goose_Pagoda.jpg Binary files differnew file mode 100644 index 0000000..668e75f --- /dev/null +++ b/static/assets/Giant_Wild_Goose_Pagoda.jpg diff --git a/static/assets/Golden_Temple_nighttime.jpg b/static/assets/Golden_Temple_nighttime.jpg Binary files differnew file mode 100644 index 0000000..08587b3 --- /dev/null +++ b/static/assets/Golden_Temple_nighttime.jpg diff --git a/static/assets/Great_Mosque_of_Xi'an_pavilion_ceiling.JPG b/static/assets/Great_Mosque_of_Xi'an_pavilion_ceiling.JPG Binary files differnew file mode 100644 index 0000000..9692a32 --- /dev/null +++ b/static/assets/Great_Mosque_of_Xi'an_pavilion_ceiling.JPG diff --git a/static/assets/Hall_of_Prayer_for_Good_Harvests_interior_2014.jpg b/static/assets/Hall_of_Prayer_for_Good_Harvests_interior_2014.jpg Binary files differnew file mode 100644 index 0000000..a8775cc --- /dev/null +++ b/static/assets/Hall_of_Prayer_for_Good_Harvests_interior_2014.jpg diff --git a/static/assets/Herod's_Temple.jpg b/static/assets/Herod's_Temple.jpg Binary files differnew file mode 100644 index 0000000..ab68794 --- /dev/null +++ b/static/assets/Herod's_Temple.jpg diff --git a/static/assets/Hoysaleshwara_temple_in_Monsoon.JPG b/static/assets/Hoysaleshwara_temple_in_Monsoon.JPG Binary files differnew file mode 100644 index 0000000..02fe08b --- /dev/null +++ b/static/assets/Hoysaleshwara_temple_in_Monsoon.JPG diff --git a/static/assets/Ibaraki_Kasugaoka_Church_light_cross.jpg b/static/assets/Ibaraki_Kasugaoka_Church_light_cross.jpg Binary files differnew file mode 100644 index 0000000..7753e1f --- /dev/null +++ b/static/assets/Ibaraki_Kasugaoka_Church_light_cross.jpg diff --git a/static/assets/Independence_-_RLDS_Temple_02.jpg b/static/assets/Independence_-_RLDS_Temple_02.jpg Binary files differnew file mode 100644 index 0000000..6a5a4db --- /dev/null +++ b/static/assets/Independence_-_RLDS_Temple_02.jpg diff --git a/static/assets/Inside_Exeter_Cathedral.jpg b/static/assets/Inside_Exeter_Cathedral.jpg Binary files differnew file mode 100644 index 0000000..6d5a303 --- /dev/null +++ b/static/assets/Inside_Exeter_Cathedral.jpg diff --git a/static/assets/Inside_the_Taj_Mahal_in_Agra,_India_Wellcome_V0046065.jpg b/static/assets/Inside_the_Taj_Mahal_in_Agra,_India_Wellcome_V0046065.jpg Binary files differnew file mode 100644 index 0000000..5c4bd6a --- /dev/null +++ b/static/assets/Inside_the_Taj_Mahal_in_Agra,_India_Wellcome_V0046065.jpg diff --git a/static/assets/Interior_of_Cathedral_of_Our_Lady_of_the_Angels_dllu.jpg b/static/assets/Interior_of_Cathedral_of_Our_Lady_of_the_Angels_dllu.jpg Binary files differnew file mode 100644 index 0000000..87afe01 --- /dev/null +++ b/static/assets/Interior_of_Cathedral_of_Our_Lady_of_the_Angels_dllu.jpg diff --git a/static/assets/Interior_of_Lotus_temple.jpg b/static/assets/Interior_of_Lotus_temple.jpg Binary files differnew file mode 100644 index 0000000..96f05c6 --- /dev/null +++ b/static/assets/Interior_of_Lotus_temple.jpg diff --git a/static/assets/Khajuraho-Lakshmana_temple.JPG b/static/assets/Khajuraho-Lakshmana_temple.JPG Binary files differnew file mode 100644 index 0000000..1f26222 --- /dev/null +++ b/static/assets/Khajuraho-Lakshmana_temple.JPG diff --git a/static/assets/King's_College_Chapel_from_The_Backs,_Cambridge,_UK.jpg b/static/assets/King's_College_Chapel_from_The_Backs,_Cambridge,_UK.jpg Binary files differnew file mode 100644 index 0000000..698cb87 --- /dev/null +++ b/static/assets/King's_College_Chapel_from_The_Backs,_Cambridge,_UK.jpg diff --git a/static/assets/Kinkaku-ji_the_Golden_Temple_in_Kyoto_overlooking_the_lake_-_high_rez.JPG b/static/assets/Kinkaku-ji_the_Golden_Temple_in_Kyoto_overlooking_the_lake_-_high_rez.JPG Binary files differnew file mode 100644 index 0000000..a5c0980 --- /dev/null +++ b/static/assets/Kinkaku-ji_the_Golden_Temple_in_Kyoto_overlooking_the_lake_-_high_rez.JPG diff --git a/static/assets/La_Cappella_degli_Scrovegni.JPG b/static/assets/La_Cappella_degli_Scrovegni.JPG Binary files differnew file mode 100644 index 0000000..9e58c48 --- /dev/null +++ b/static/assets/La_Cappella_degli_Scrovegni.JPG diff --git a/static/assets/Lakshmana_Temple_12.jpg b/static/assets/Lakshmana_Temple_12.jpg Binary files differnew file mode 100644 index 0000000..2789b53 --- /dev/null +++ b/static/assets/Lakshmana_Temple_12.jpg diff --git a/static/assets/Lombardia_Mantova5_tango7174.jpg b/static/assets/Lombardia_Mantova5_tango7174.jpg Binary files differnew file mode 100644 index 0000000..2e5e439 --- /dev/null +++ b/static/assets/Lombardia_Mantova5_tango7174.jpg diff --git a/static/assets/LotusDelhi.jpg b/static/assets/LotusDelhi.jpg Binary files differnew file mode 100644 index 0000000..485e958 --- /dev/null +++ b/static/assets/LotusDelhi.jpg diff --git a/static/assets/Luxor,_Luxor_Temple,_west_side_view,_Egypt,_Oct_2004.jpg b/static/assets/Luxor,_Luxor_Temple,_west_side_view,_Egypt,_Oct_2004.jpg Binary files differnew file mode 100644 index 0000000..c1dd1ec --- /dev/null +++ b/static/assets/Luxor,_Luxor_Temple,_west_side_view,_Egypt,_Oct_2004.jpg diff --git a/static/assets/Luxor_Temple_Obelisk.JPG b/static/assets/Luxor_Temple_Obelisk.JPG Binary files differnew file mode 100644 index 0000000..f4be113 --- /dev/null +++ b/static/assets/Luxor_Temple_Obelisk.JPG diff --git a/static/assets/MaisonCarrée.jpeg b/static/assets/MaisonCarrée.jpeg Binary files differnew file mode 100644 index 0000000..2f1d935 --- /dev/null +++ b/static/assets/MaisonCarrée.jpeg diff --git a/static/assets/MantovaBasilicaSantAndrea_cutnpaste_over_intrusions.jpg b/static/assets/MantovaBasilicaSantAndrea_cutnpaste_over_intrusions.jpg Binary files differnew file mode 100644 index 0000000..6395e96 --- /dev/null +++ b/static/assets/MantovaBasilicaSantAndrea_cutnpaste_over_intrusions.jpg diff --git a/static/assets/Mission_San_Diego_de_Alcalá_-_church.jpg b/static/assets/Mission_San_Diego_de_Alcalá_-_church.jpg Binary files differnew file mode 100644 index 0000000..9001800 --- /dev/null +++ b/static/assets/Mission_San_Diego_de_Alcalá_-_church.jpg diff --git a/static/assets/MonrealeCathedral-pjt1.jpg b/static/assets/MonrealeCathedral-pjt1.jpg Binary files differnew file mode 100644 index 0000000..966eab9 --- /dev/null +++ b/static/assets/MonrealeCathedral-pjt1.jpg diff --git a/static/assets/Monreale_Cathedral_exterior_BW_2012-10-09_10-23-10.jpg b/static/assets/Monreale_Cathedral_exterior_BW_2012-10-09_10-23-10.jpg Binary files differnew file mode 100644 index 0000000..b0cb052 --- /dev/null +++ b/static/assets/Monreale_Cathedral_exterior_BW_2012-10-09_10-23-10.jpg diff --git a/static/assets/Nagasaki_Kofukuji_M5667.jpg b/static/assets/Nagasaki_Kofukuji_M5667.jpg Binary files differnew file mode 100644 index 0000000..63544ee --- /dev/null +++ b/static/assets/Nagasaki_Kofukuji_M5667.jpg diff --git a/static/assets/NaraTodaijiDaibutsu0212.jpg b/static/assets/NaraTodaijiDaibutsu0212.jpg Binary files differnew file mode 100644 index 0000000..b4f3af4 --- /dev/null +++ b/static/assets/NaraTodaijiDaibutsu0212.jpg diff --git a/static/assets/Olympieion2_copy.jpg b/static/assets/Olympieion2_copy.jpg Binary files differnew file mode 100644 index 0000000..ee13f3d --- /dev/null +++ b/static/assets/Olympieion2_copy.jpg diff --git a/static/assets/Padova_Cappella_degli_Scrovegni_Innen_Langhaus_West_1.jpg b/static/assets/Padova_Cappella_degli_Scrovegni_Innen_Langhaus_West_1.jpg Binary files differnew file mode 100644 index 0000000..d1c6ed1 --- /dev/null +++ b/static/assets/Padova_Cappella_degli_Scrovegni_Innen_Langhaus_West_1.jpg diff --git a/static/assets/Pagoda_at_Xingshengjiao_Temple.jpg b/static/assets/Pagoda_at_Xingshengjiao_Temple.jpg Binary files differnew file mode 100644 index 0000000..421b8a4 --- /dev/null +++ b/static/assets/Pagoda_at_Xingshengjiao_Temple.jpg diff --git a/static/assets/Pagoda_of_Songyue_Temple,_2015-09-25_08.jpg b/static/assets/Pagoda_of_Songyue_Temple,_2015-09-25_08.jpg Binary files differnew file mode 100644 index 0000000..a21c3fa --- /dev/null +++ b/static/assets/Pagoda_of_Songyue_Temple,_2015-09-25_08.jpg diff --git a/static/assets/Pagoda_of_Songyue_Temple,_2015-09-25_20.jpg b/static/assets/Pagoda_of_Songyue_Temple,_2015-09-25_20.jpg Binary files differnew file mode 100644 index 0000000..f85e229 --- /dev/null +++ b/static/assets/Pagoda_of_Songyue_Temple,_2015-09-25_20.jpg diff --git a/static/assets/Patio_de_los_leones.jpg b/static/assets/Patio_de_los_leones.jpg Binary files differnew file mode 100644 index 0000000..b5b11b7 --- /dev/null +++ b/static/assets/Patio_de_los_leones.jpg diff --git a/static/assets/Pazzi_Chapel_Florence_Apr_2008.jpg b/static/assets/Pazzi_Chapel_Florence_Apr_2008.jpg Binary files differnew file mode 100644 index 0000000..6993d7b --- /dev/null +++ b/static/assets/Pazzi_Chapel_Florence_Apr_2008.jpg diff --git a/static/assets/Pazzi_Chapel_Santa_Croce_Apr_2008_P.JPG b/static/assets/Pazzi_Chapel_Santa_Croce_Apr_2008_P.JPG Binary files differnew file mode 100644 index 0000000..5ae36f9 --- /dev/null +++ b/static/assets/Pazzi_Chapel_Santa_Croce_Apr_2008_P.JPG diff --git a/static/assets/Pergamonmuseum_-_Antikensammlung_-_Pergamonaltar_02-03.jpg b/static/assets/Pergamonmuseum_-_Antikensammlung_-_Pergamonaltar_02-03.jpg Binary files differnew file mode 100644 index 0000000..8ed13cf --- /dev/null +++ b/static/assets/Pergamonmuseum_-_Antikensammlung_-_Pergamonaltar_02-03.jpg diff --git a/static/assets/Ravenna_BW_1.JPG b/static/assets/Ravenna_BW_1.JPG Binary files differnew file mode 100644 index 0000000..936dab3 --- /dev/null +++ b/static/assets/Ravenna_BW_1.JPG diff --git a/static/assets/Salt_Lake_Temple,_Utah_-_Sept_2004-2.jpg b/static/assets/Salt_Lake_Temple,_Utah_-_Sept_2004-2.jpg Binary files differnew file mode 100644 index 0000000..c923812 --- /dev/null +++ b/static/assets/Salt_Lake_Temple,_Utah_-_Sept_2004-2.jpg diff --git a/static/assets/Salt_Lake_Temple_model_-_2_March_2013.jpg b/static/assets/Salt_Lake_Temple_model_-_2_March_2013.jpg Binary files differnew file mode 100644 index 0000000..bed0e37 --- /dev/null +++ b/static/assets/Salt_Lake_Temple_model_-_2_March_2013.jpg diff --git a/static/assets/Salzburg_Cathedral_1.jpg b/static/assets/Salzburg_Cathedral_1.jpg Binary files differnew file mode 100644 index 0000000..54bff65 --- /dev/null +++ b/static/assets/Salzburg_Cathedral_1.jpg diff --git a/static/assets/San_Francisco_japantowns_peace_tower.jpg b/static/assets/San_Francisco_japantowns_peace_tower.jpg Binary files differnew file mode 100644 index 0000000..af3bc8e --- /dev/null +++ b/static/assets/San_Francisco_japantowns_peace_tower.jpg diff --git a/static/assets/Serpent_head_at_the_base_of_El_Castillo.jpg b/static/assets/Serpent_head_at_the_base_of_El_Castillo.jpg Binary files differnew file mode 100644 index 0000000..76cf690 --- /dev/null +++ b/static/assets/Serpent_head_at_the_base_of_El_Castillo.jpg diff --git a/static/assets/St_Paul's_Cathedral_Nave,_London,_UK_-_Diliff.jpg b/static/assets/St_Paul's_Cathedral_Nave,_London,_UK_-_Diliff.jpg Binary files differnew file mode 100644 index 0000000..5aec27e --- /dev/null +++ b/static/assets/St_Paul's_Cathedral_Nave,_London,_UK_-_Diliff.jpg diff --git a/static/assets/St_Pauls_aerial_(cropped).jpg b/static/assets/St_Pauls_aerial_(cropped).jpg Binary files differnew file mode 100644 index 0000000..0c08ee0 --- /dev/null +++ b/static/assets/St_Pauls_aerial_(cropped).jpg diff --git a/static/assets/Statue_in_Cambodia.jpg b/static/assets/Statue_in_Cambodia.jpg Binary files differnew file mode 100644 index 0000000..db58f73 --- /dev/null +++ b/static/assets/Statue_in_Cambodia.jpg diff --git a/static/assets/Stift_Melk,_Westansicht.jpg b/static/assets/Stift_Melk,_Westansicht.jpg Binary files differnew file mode 100644 index 0000000..9175acb --- /dev/null +++ b/static/assets/Stift_Melk,_Westansicht.jpg diff --git a/static/assets/Taj-Mahal.jpg b/static/assets/Taj-Mahal.jpg Binary files differnew file mode 100644 index 0000000..df91986 --- /dev/null +++ b/static/assets/Taj-Mahal.jpg diff --git a/static/assets/Temptation_of_the_Buddha_with_Mara_and_his_daughters_and_the_demons_of_Mara_fleeing_Sanchi_Stupa_1_Northern_Gateway.jpg b/static/assets/Temptation_of_the_Buddha_with_Mara_and_his_daughters_and_the_demons_of_Mara_fleeing_Sanchi_Stupa_1_Northern_Gateway.jpg Binary files differnew file mode 100644 index 0000000..c6ff86c --- /dev/null +++ b/static/assets/Temptation_of_the_Buddha_with_Mara_and_his_daughters_and_the_demons_of_Mara_fleeing_Sanchi_Stupa_1_Northern_Gateway.jpg diff --git a/static/assets/Teotihuacan,_Citadel,_Temple_of_the_Feathered_Serpent_(20686669345).jpg b/static/assets/Teotihuacan,_Citadel,_Temple_of_the_Feathered_Serpent_(20686669345).jpg Binary files differnew file mode 100644 index 0000000..3f20c95 --- /dev/null +++ b/static/assets/Teotihuacan,_Citadel,_Temple_of_the_Feathered_Serpent_(20686669345).jpg diff --git a/static/assets/Teotihuacán,_México,_2013-10-13,_DD_80.JPG b/static/assets/Teotihuacán,_México,_2013-10-13,_DD_80.JPG Binary files differnew file mode 100644 index 0000000..bd4ae90 --- /dev/null +++ b/static/assets/Teotihuacán,_México,_2013-10-13,_DD_80.JPG diff --git a/static/assets/The_interior_view_of_Charminar.jpg b/static/assets/The_interior_view_of_Charminar.jpg Binary files differnew file mode 100644 index 0000000..263c206 --- /dev/null +++ b/static/assets/The_interior_view_of_Charminar.jpg diff --git a/static/assets/Tōdai-ji_Kon-dō.jpg b/static/assets/Tōdai-ji_Kon-dō.jpg Binary files differnew file mode 100644 index 0000000..6e01b5b --- /dev/null +++ b/static/assets/Tōdai-ji_Kon-dō.jpg diff --git a/static/assets/View_of_Santa_Maria_del_Fiore_in_Florence.jpg b/static/assets/View_of_Santa_Maria_del_Fiore_in_Florence.jpg Binary files differnew file mode 100644 index 0000000..a7b42e7 --- /dev/null +++ b/static/assets/View_of_Santa_Maria_del_Fiore_in_Florence.jpg diff --git a/static/assets/Xian_Mosque3.jpg b/static/assets/Xian_Mosque3.jpg Binary files differnew file mode 100644 index 0000000..ac073d3 --- /dev/null +++ b/static/assets/Xian_Mosque3.jpg diff --git a/static/favicon.ico b/static/favicon.ico Binary files differnew file mode 100644 index 0000000..cf8ac09 --- /dev/null +++ b/static/favicon.ico diff --git a/static/manifest.toml b/static/manifest.toml new file mode 100644 index 0000000..d6ccae9 --- /dev/null +++ b/static/manifest.toml @@ -0,0 +1,680 @@ +[[mediums]] +tag = "ReligiousArchitecture" +label = "Religious architecture" +description = "Temples, mosques, stupas, cathedrals." +disabled = false + +[[mediums.works]] +name = "Erechtheion" +year = -421 +location = "Athens, Greece" +wiki = "https://en.wikipedia.org/wiki/Erechtheion" +[[mediums.works.figures]] +file = "1280px-Erechtheum_Acropolis_Athens.jpg" +byline = "CC0 1.0 Jebulon" +[[mediums.works.figures]] +file = "1280px-Athen_Erechtheion_BW_2017-10-09_13-58-34.jpg" +byline = "CC BY-SA 3.0 Berthold Werner" + +[[mediums.works]] +name = "Temple of Hephaestus" +year = -449 +location = "Athens, Greece" +wiki = "https://en.wikipedia.org/wiki/Temple_of_Hephaestus" +[[mediums.works.figures]] +file = "1280px-Temple_of_Hephaestus_in_Athens_20180221-2.jpg" +byline = "CC BY-SA 4.0 Suicasmo" +[[mediums.works.figures]] +file = "1280px-Temple_of_Hephaestus_in_Athens_20180221-1.jpg" +byline = "CC BY-SA 4.0 Suicasmo" + +[[mediums.works]] +name = "Luxor Temple" +year = -1400 +location = "Thebes, Egypt" +wiki = "https://en.wikipedia.org/wiki/Luxor_Temple" +[[mediums.works.figures]] +file = "Luxor,_Luxor_Temple,_west_side_view,_Egypt,_Oct_2004.jpg" +byline = "CC BY-SA 2.0 Przemyslaw \"Blueshade\" Idzkiewicz" +[[mediums.works.figures]] +file = "Luxor_Temple_Obelisk.JPG" +byline = "Public domain Charlesdrakew" + +[[mediums.works]] +name = "Pantheon" +year = 113 +location = "Rome, Italy" +wiki = "https://en.wikipedia.org/wiki/Pantheon,_Rome" +[[mediums.works.figures]] +file = "1280px-Pantheon_Rom_1_cropped.jpg" +byline = "CC BY-SA 4.0 Rabax63" +[[mediums.works.figures]] +file = "1280px-Dome_of_Pantheon_Rome.JPG" +byline = "Public domain Dave Amos" + +[[mediums.works]] +name = "Parthenon" +year = -447 +location = "Athens, Greece" +wiki = "https://en.wikipedia.org/wiki/Parthenon" +[[mediums.works.figures]] +file = "1280px-Parthenon_from_west.jpg" +byline = "Public domain Mountain" +[[mediums.works.figures]] +file = "1280px-Parthenon,_Acropolis,_Athens,_Greece.jpg" +byline = "CC BY-SA 2.0 Jim Killock" + +[[mediums.works]] +name = "Pergamon Altar" +year = -166 +location = "Pergamon (present-day Turkey)" +wiki = "https://en.wikipedia.org/wiki/Pergamon_Altar" +[[mediums.works.figures]] +file = "Berlin_-_Pergamonmuseum_-_Altar_01.jpg" +byline = "CC BY-SA 3.0 Lestat (Jan Mehlich)" +[[mediums.works.figures]] +file = "Pergamonmuseum_-_Antikensammlung_-_Pergamonaltar_02-03.jpg" +byline = "GNU FDL Unknown" + +[[mediums.works]] +name = "Temple of Zeus at Olympia" +year = -470 +location = "Olympia, Greece" +wiki = "https://en.wikipedia.org/wiki/Temple_of_Zeus,_Olympia" +[[mediums.works.figures]] +file = "Attica_06-13_Athens_25_Olympian_Zeus_Temple.jpg" +byline = "CC BY-SA 3.0 A.Savin" +[[mediums.works.figures]] +file = "Olympieion2_copy.jpg" +byline = "CC BY-SA 4.0 Valentin Fiumefreddo (probable reconstruction)" + +[[mediums.works]] +name = "Maison Carrée" +year = 2 +location = "Nîmes, France" +wiki = "https://en.wikipedia.org/wiki/Maison_Carr%C3%A9e" +[[mediums.works.figures]] +file = "MaisonCarrée.jpeg" +byline = "Public domain Danichou" + +[[mediums.works]] +name = "Dura-Europos Synagogue" +year = 244 +location = "Dura-Europos, Syria" +wiki = "https://en.wikipedia.org/wiki/Dura-Europos_synagogue" +[[mediums.works.figures]] +file = "Doura_Europos_synagogue_courtyard.jpg" +byline = "CC BY-SA 3.0 Marsyas" +[[mediums.works.figures]] +file = "Herod's_Temple.jpg" +byline = "Public domain Unknown" + +[[mediums.works]] +name = "Basilica of Sant’Apollinare in Classe" +year = 549 +location = "Ravenna, Italy" +wiki = "https://en.wikipedia.org/wiki/Basilica_of_Sant%27Apollinare_in_Classe" +[[mediums.works.figures]] +file = "2012_ravenna_133.jpg" +byline = "CC BY-SA 3.0 Sansa55" +[[mediums.works.figures]] +file = "Ravenna_BW_1.JPG" +byline = "CC0 Berthold Werner" +[[mediums.works.figures]] +file = "3456px-Nave_of_Basilica_of_Sant'Apollinare_in_Classe,_Ravenna,_Italy.JPG" +byline = "CC BY-SA 4.0 Berkay0652" + +[[mediums.works]] +name = "Aachen Cathedral" +year = 796 +location = "Aachen, Germany" +wiki = "https://en.wikipedia.org/wiki/Aachen_Cathedral" +[[mediums.works.figures]] +file = "Aachen_Germany_Imperial-Cathedral-01.jpg" +byline = "CC BY-SA 3.0 CEphoto, Uwe Aranas" +[[mediums.works.figures]] +file = "Aachener_Dom_BW_2016-07-09_16-20-40.jpg" +byline = "CC BY-SA 3.0 Berthold Werner" +[[mediums.works.figures]] +file = "AachenCathedralMainPortalHDR.jpg" +byline = "CC BY-SA 2.5 maxgreene" + +[[mediums.works]] +name = "All Saints’ Church" +year = 970 +location = "Earls Barton, England" +wiki = "https://en.wikipedia.org/wiki/All_Saints%27_Church,_Earls_Barton" +[[mediums.works.figures]] +file = "EarlsBartonChurch.JPG" +byline = "CC BY-SA 2.5 R Neil Marshman" + +[[mediums.works]] +name = "Durham Cathedral" +year = 1093 +location = "Durham, England" +wiki = "https://en.wikipedia.org/wiki/Durham_Cathedral" +[[mediums.works.figures]] +file = "Durham_MMB_02_Cathedral.jpg" +byline = "CC BY-SA 4.0 mattbuck" +[[mediums.works.figures]] +file = "Durham_Cathedral._Interior.jpg" +byline = "CC BY-SA 3.0 Oliver-Bonjoch" + +[[mediums.works]] +name = "Notre-Dame" +year = 1163 +location = "Paris, France" +wiki = "https://en.wikipedia.org/wiki/Notre-Dame_de_Paris" +[[mediums.works.figures]] +file = "Cath%C3%A9drale_Notre-Dame_de_Paris%2C_3_June_2010.jpg" +byline = "CC BY-SA 2.0 sacratomato_hr" +[[mediums.works.figures]] +file = "Cath%C3%A9drale_Notre-Dame_de_Paris_-_15.jpg" +byline = "CC BY-SA 3.0 Carlos Delgado" + +[[mediums.works]] +name = "Saint Trophimus’ Church" +year = 770 +location = "Eschau, France" +wiki = "https://en.wikipedia.org/wiki/St_Trophimus%27_Church,_Eschau" +[[mediums.works.figures]] +file = "Abbatiale_Sainte_Trophime_d%27Eschau_%281%29.jpg" +byline = "CC BY-SA 3.0 J.schahl.87" +[[mediums.works.figures]] +file = "Eglise_Saint-Trophime%2C_Eschau_4.JPG" +byline = "CC BY-SA 4.0 Chris06" + +[[mediums.works]] +name = "Alhambra" +year = 889 +location = "Granada, Spain" +wiki = "https://en.wikipedia.org/wiki/Alhambra" +[[mediums.works.figures]] +file = "Dawn_Charles_V_Palace_Alhambra_Granada_Andalusia_Spain.jpg" +byline = "CC0 Jebulon" +[[mediums.works.figures]] +file = "Patio_de_los_leones.jpg" +byline = "CC BY 2.0 Jim Gordon" + +[[mediums.works]] +name = "King’s College Chapel" +year = 1443 +location = "Cambridge, England" +wiki = "https://en.wikipedia.org/wiki/King%27s_College_Chapel,_Cambridge" +[[mediums.works.figures]] +file = "King%27s_College_Chapel_from_The_Backs%2C_Cambridge%2C_UK.jpg" +byline = "GPL3 Unknown" +[[mediums.works.figures]] +file = "Cambridge_King%27s_College_Chapel.jpg" +byline = "CC BY-SA 4.0 Cc364" + +[[mediums.works]] +name = "Melk Abbey" +year = 1089 +location = "Melk, Austria" +wiki = "https://en.wikipedia.org/wiki/Melk_Abbey" +[[mediums.works.figures]] +file = "Stift_Melk%2C_Westansicht.jpg" +byline = "CC BY-SA 4.0 Thomas Ledl" +[[mediums.works.figures]] +file = "070526_Stift_Melk_02.jpg" +byline = "CC BY-SA 3.0 Aconcagua" + +[[mediums.works]] +name = "Monreale Cathedral" +year = 1172 +location = "Monreale, Italy" +wiki = "https://en.wikipedia.org/wiki/Monreale_Cathedral" +[[mediums.works.figures]] +file = "Monreale_Cathedral_exterior_BW_2012-10-09_10-23-10.jpg" +byline = "CC BY-SA 3.0 Berthold Werner" +[[mediums.works.figures]] +file = "MonrealeCathedral-pjt1.jpg" +byline = "CC BY-SA 3.0 pjt56" + +[[mediums.works]] +name = "Amiens Cathedral" +year = 1220 +location = "Amiens, France" +wiki = "https://en.wikipedia.org/wiki/Amiens_Cathedral" +[[mediums.works.figures]] +file = "0_Amiens_-_Cath%C3%A9drale_Notre-Dame_%281%29.JPG" +byline = "CC BY 3.0 Jean-Pol GRANDMONT" +[[mediums.works.figures]] +file = "Amiens_Cathedral_choir_Wikimedia_Commons.jpg" +byline = "CC BY-SA 3.0 Benh LIEU SONG" + +[[mediums.works]] +name = "Arena Chapel" +year = 1305 +location = "Padua, Italy" +wiki = "https://en.wikipedia.org/wiki/Scrovegni_Chapel" +[[mediums.works.figures]] +file = "La_Cappella_degli_Scrovegni.JPG" +byline = "GNU FDL Andrea Piroddi" +[[mediums.works.figures]] +file = "Padova_Cappella_degli_Scrovegni_Innen_Langhaus_West_1.jpg" +byline = "CC BY-SA 4.0 Zairon" + +[[mediums.works]] +name = "Exeter Cathedral" +year = 1258 +location = "Exeter, England" +wiki = "https://en.wikipedia.org/wiki/Exeter_Cathedral" +[[mediums.works.figures]] +file = "Exeter-28Ap11-wyrdlight.jpg" +byline = "CC BY-SA 3.0 Antony McCallum" +[[mediums.works.figures]] +file = "Inside_Exeter_Cathedral.jpg" +byline = "CC BY-SA 4.0 Edward Swift" + +[[mediums.works]] +name = "Florence Cathedral" +year = 1436 +location = "Florence, Italy" +wiki = "https://en.wikipedia.org/wiki/Florence_Cathedral" +[[mediums.works.figures]] +file = "View_of_Santa_Maria_del_Fiore_in_Florence.jpg" +byline = "CC BY-SA 2.0 Bruce Stokes on Flickr" +[[mediums.works.figures]] +file = "Duomo_Firenze_Apr_2008.jpg" +byline = "CC BY-SA 3.0 Gryffindor" + +[[mediums.works]] +name = "Pazzi Chapel" +year = 1442 +location = "Florence, Italy" +wiki = "https://en.wikipedia.org/wiki/Pazzi_Chapel" +[[mediums.works.figures]] +file = "Pazzi_Chapel_Santa_Croce_Apr_2008_P.JPG" +byline = "GNU FDL Gryffindor" +[[mediums.works.figures]] +file = "Pazzi_Chapel_Florence_Apr_2008.jpg" +byline = "CC BY-SA 3.0 Gryffindor" + +[[mediums.works]] +name = "Basilica di Sant’Andrea" +year = 1472 +location = "Mantua, Italy" +wiki = "https://en.wikipedia.org/wiki/Basilica_of_Sant%27Andrea,_Mantua" +[[mediums.works.figures]] +file = "MantovaBasilicaSantAndrea_cutnpaste_over_intrusions.jpg" +byline = "Public domain Sebi1" +[[mediums.works.figures]] +file = "Lombardia_Mantova5_tango7174.jpg" +byline = "CC BY-SA 4.0 Tango7174" + +[[mediums.works]] +name = "Church of the Gesù" +year = 1568 +location = "Rome, Italy" +wiki = "https://en.wikipedia.org/wiki/Church_of_the_Ges%C3%B9" +[[mediums.works.figures]] +file = "Church_of_the_Ges%C3%B9%2C_Rome.jpg" +byline = "CC BY-SA 3.0 Alessio Damato" +[[mediums.works.figures]] +file = "Chiesa_del_Ges%C3%B9_September_2015-1a.jpg" +byline = "CC BY-SA 4.0 Alvesgaspar" + +[[mediums.works]] +name = "St Paul’s Cathedral" +year = 1675 +location = "London, England" +wiki = "https://en.wikipedia.org/wiki/St_Paul%27s_Cathedral" +[[mediums.works.figures]] +file = "St_Pauls_aerial_%28cropped%29.jpg" +byline = "CC BY 2.0 Mark Fosh" +[[mediums.works.figures]] +file = "St_Paul%27s_Cathedral_Nave%2C_London%2C_UK_-_Diliff.jpg" +byline = "Diliff" + +[[mediums.works]] +name = "Basilica of San Vitale" +year = 527 +location = "Ravenna, Italy" +wiki = "https://en.wikipedia.org/wiki/Basilica_of_San_Vitale" +[[mediums.works.figures]] +file = "File:Basilica_of_San_Vitale,_Ravenna,_Italy.jpg" +byline = "CC BY-SA 4.0 Tango7174" + +[[mediums.works]] +name = "Dome of the Rock" +year = 688 +location = "Jerusalem" +wiki = "https://en.wikipedia.org/wiki/Dome_of_the_Rock" + +[[mediums.works]] +name = "Salt Lake Temple" +year = 1893 +location = "Salt Lake City, United States" +wiki = "https://en.wikipedia.org/wiki/File:Salt_Lake_Temple,_Utah_-_Sept_2004-2.jpg" +[[mediums.works.figures]] +file = "Salt_Lake_Temple%2C_Utah_-_Sept_2004-2.jpg" +byline = "CC BY-SA 3.0 Entheta" +[[mediums.works.figures]] +file = "Salt_Lake_Temple_model_-_2_March_2013.jpg" +byline = "CC BY 2.0 Model: Peter McCann Architectural Models" + +[[mediums.works]] +name = "Lotus Temple" +year = 1986 +location = "Delhi, India" +wiki = "https://en.wikipedia.org/wiki/File:LotusDelhi.jpg" +[[mediums.works.figures]] +file = "LotusDelhi.jpg" +byline = "CC BY 2.0 Vandelizer" +[[mediums.works.figures]] +file = "Interior_of_Lotus_temple.jpg" +byline = "CC BY 2.0 Dinudey Baidya" + +[[mediums.works]] +name = "Salzburg Cathedral" +year = 1614 +location = "Salzburg, Germany" +wiki = "https://en.wikipedia.org/wiki/Salzburg_Cathedral" +[[mediums.works.figures]] +file = "Salzburg_Cathedral_1.jpg" +byline = "CC BY-SA 3.0 Bede735c" +[[mediums.works.figures]] +file = "Catedral_de_Salzburgo%2C_Salzburgo%2C_Austria%2C_2019-05-19%2C_DD_08.jpg" +byline = "CC BY-SA 4.0 Diego Delso" + +[[mediums.works]] +name = "Cathedral of Our Lady of the Angels" +year = 2002 +location = "Los Angeles, United States" +wiki = "Cathedral of Our Lady of the Angels" +[[mediums.works.figures]] +file = "Cathedral_of_Our_Lady_of_Angels%2C_Los_Angeles.JPG" +byline = "CC BY-SA 4.0 Los Angeles" +[[mediums.works.figures]] +file = "Interior_of_Cathedral_of_Our_Lady_of_the_Angels_dllu.jpg" +byline = "CC BY-SA 4.0 Daniel L. Lu (user:dllu)" + +[[mediums.works]] +name = "Jasna Góra Monastery" +year = 1382 +location = "Częstochowa, Poland" +wiki = "Częstochowa, Poland" +[[mediums.works.figures]] +file = "Cz%C4%99stochowa_klasztor_Jasna_G%C3%B3ra-2162.jpg" +byline = "CC BY-SA 3.0 plJerzy Szota" +[[mediums.works.figures]] +file = "Czestochowa-bazylika.jpg" +byline = "CC BY-SA 2.5 Skarabeusz" + +[[mediums.works]] +name = "Independence Temple" +year = 1990 +location = "Independence, Missouri, United States" +wiki = "https://en.wikipedia.org/wiki/Independence_Temple" +[[mediums.works.figures]] +file = "Independence_-_RLDS_Temple_02.jpg" +byline = "Public domain Ecjmartin1" + +[[mediums.works]] +name = "Angkor Wat" +year = 1160 +location = "Siem Reap, Cambodia" +wiki = "https://en.wikipedia.org/wiki/Angkor_Wat" +[[mediums.works.figures]] +file = "Angkor_Vat_%286931599619%29.jpg" +byline = "CC BY 2.0 Jean-Pierre Dalbéra" +[[mediums.works.figures]] +file = "Angkor-Wat-from-the-air.JPG" +byline = "CC BY 2.5 Charles J Sharp" +[[mediums.works.figures]] +file = "Statue_in_Cambodia.jpg" +byline = "CC BY-SA 2.0 mark sebastian" + +[[mediums.works]] +name = "Ryōan-ji" +year = 1488 +location = "Kyoto, Japan" +wiki = "https://en.wikipedia.org/wiki/Ry%C5%8Dan-ji" +[[mediums.works.figures]] +file = "Cherry_blossom_at_the_rock_garden_of_Ry%C5%8Dan-ji_Temple_in_Kyoto%2C_Japan.jpg" +byline = "CC BY-SA 4.0 Didier Moïse" + +[[mediums.works]] +name = "Tōdai-ji" +year = 738 +location = "Nara, Japan" +wiki = "https://en.wikipedia.org/wiki/T%C5%8Ddai-ji" +[[mediums.works.figures]] +file = "T%C5%8Ddai-ji_Kon-d%C5%8D.jpg" +byline = "CC BY-SA 3.0 Wiiii" +[[mediums.works.figures]] +file = "NaraTodaijiDaibutsu0212.jpg" +byline = "Public domain Unknown" + +[[mediums.works]] +name = "Kinkaku-ji" +year = 1397 +location = "Kyoto, Japan" +wiki = "Kinkaku-ji" +[[mediums.works.figures]] +file = "Kinkaku-ji_the_Golden_Temple_in_Kyoto_overlooking_the_lake_-_high_rez.JPG" +byline = "CC BY-SA 3.0 Jaycangel" + +[[mediums.works]] +name = "Kofukuji" +year = 1624 +location = "Nagasaki, Japan" +wiki = "https://en.wikipedia.org/wiki/Kofukuji_(Nagasaki)" +[[mediums.works.figures]] +file = "Nagasaki_Kofukuji_M5667.jpg" +byline = "Public domain Fg2" + +[[mediums.works]] +name = "Peace Pagoda" +year = 1968 +location = "San Francisco, United States" +wiki = "https://en.wikipedia.org/wiki/San_Francisco_Peace_Pagoda" +[[mediums.works.figures]] +file = "San_Francisco_japantowns_peace_tower.jpg" +byline = "Public domain Erik Harmon" + +[[mediums.works]] +name = "Songyue Pagoda" +year = 523 +location = "Mount Song, China" +wiki = "https://en.wikipedia.org/wiki/Songyue_Pagoda" +[[mediums.works.figures]] +file = "Pagoda_of_Songyue_Temple%2C_2015-09-25_20.jpg" +byline = "CC BY-SA 4.0 Siyuwj" +[[mediums.works.figures]] +file = "Pagoda_of_Songyue_Temple%2C_2015-09-25_08.jpg" +byline = "CC BY-SA 4.0 Siyuwj" + +[[mediums.works]] +name = "Church of the Light" +year = 1989 +location = "Ibaraki, Japan" +wiki = "https://en.wikipedia.org/wiki/Church_of_the_Light" +[[mediums.works.figures]] +file = "Ibaraki_Kasugaoka_Church_light_cross.jpg" +byline = "GNU FDL Bergmann" + +[[mediums.works]] +name = "Mission San Diego de Alcalá" +year = 1769 +location = "San Diego, United States" +wiki = "https://en.wikipedia.org/wiki/Mission_San_Diego_de_Alcal%C3%A1" +[[mediums.works.figures]] +file = "Mission_San_Diego_de_Alcal%C3%A1_-_church.jpg" +byline = "CC BY-SA 3.0 Bernard Gagnon" + +[[mediums.works]] +name = "Temple of Heaven" +year = 1998 +location = "Beijing, China" +wiki = "https://en.wikipedia.org/wiki/Temple_of_Heaven" +[[mediums.works.figures]] +file = "11_Temple_of_Heaven.jpg" +byline = "CC BY-SA 2.0 Philip Larson" +[[mediums.works.figures]] +file = "Hall_of_Prayer_for_Good_Harvests_interior_2014.jpg" +byline = "CC BY-SA 3.0 Daniel Case" + +[[mediums.works]] +name = "Giant Wild Goose Pagoda" +year = 704 +location = "Xi’an, China" +wiki = "https://en.wikipedia.org/wiki/Giant_Wild_Goose_Pagoda" +[[mediums.works.figures]] +file = "Giant_Wild_Goose_Pagoda.jpg" +byline = "CC BY-SA 2.5 Alex Kwok" + +[[mediums.works]] +name = "El Castillo" +year = 950 +location = "Chichen Itza, Mexico" +wiki = "https://en.wikipedia.org/wiki/El_Castillo,_Chichen_Itza" +[[mediums.works.figures]] +file = "Chichen_Itza_%283326547826%29.jpg" +byline = "CC BY-SA 2.0 Alastair Rae" +[[mediums.works.figures]] +file = "Serpent_head_at_the_base_of_El_Castillo.jpg" +byline = "CC BY 2.0 Frank Kovalchek" + +[[mediums.works]] +name = "Temple of the Feathered Serpent" +year = 175 +location = "Teotihuacan, Mexico" +wiki = "https://en.wikipedia.org/wiki/Temple_of_the_Feathered_Serpent,_Teotihuacan" +[[mediums.works.figures]] +file = "Teotihuac%C3%A1n%2C_M%C3%A9xico%2C_2013-10-13%2C_DD_80.JPG" +byline = "CC BY-SA 3.0 " +[[mediums.works.figures]] +file = "Teotihuacan%2C_Citadel%2C_Temple_of_the_Feathered_Serpent_%2820686669345%29.jpg" +byline = "CC BY 2.0 Arian Zwegers" + +[[mediums.works]] +name = "Ziggurat of Ur" +year = -2150 +location = "Ur, Iraq" +wiki = "https://en.wikipedia.org/wiki/Ziggurat_of_Ur" +[[mediums.works.figures]] +file = "Ancient_ziggurat_at_Ali_Air_Base_Iraq_2005.jpg" +byline = "CC BY 3.0 en:User:Hardnfast" + +[[mediums.works]] +name = "Taj Mahal" +year = 1632 +location = "Agra, India" +wiki = "https://en.wikipedia.org/wiki/Taj_Mahal" +[[mediums.works.figures]] +file = "Taj-Mahal.jpg" +byline = "CC BY-SA 4.0 Joel Godwin" +[[mediums.works.figures]] +file = "Inside_the_Taj_Mahal_in_Agra%2C_India_Wellcome_V0046065.jpg" +byline = "CC BY 4.0 Wellcome Collection" + +[[mediums.works]] +name = "Lakshmana Temple" +year = 930 +location = "Khajuraho, India" +wiki = "https://en.wikipedia.org/wiki/Lakshmana_Temple,_Khajuraho" +[[mediums.works.figures]] +file = "Khajuraho-Lakshmana_temple.JPG" +byline = "Christopher Voitus" +[[mediums.works.figures]] +file = "Lakshmana_Temple_12.jpg" +byline = "CC BY-SA 3.0 Antoine Taveneaux" + +[[mediums.works]] +name = "Dashavatara Temple" +year = 500 +location = "Deogarh, India" +wiki = "https://en.wikipedia.org/wiki/Dashavatara_Temple,_Deogarh" +[[mediums.works.figures]] +file = "Deogarh01.jpg" +byline = "CC BY-SA 2.0 byron aihara" +[[mediums.works.figures]] +file = "Door_Desavatara_Deogarh.jpg" +byline = "CC BY 2.0 Bob King" + +[[mediums.works]] +name = "Hoysaleswara Temple" +year = 1121 +location = "Halebidu, India" +wiki = "https://en.wikipedia.org/wiki/Hoysaleswara_Temple" +[[mediums.works.figures]] +file = "Hoysaleshwara_temple_in_Monsoon.JPG" +byline = "CC BY-SA 3.0 Karthikbs23" +[[mediums.works.figures]] +file = "12th-century_first_Nandi_facing_Shiva_shrine_at_Shaivism_Hindu_temple_Hoysaleswara_arts_Halebidu_Karnataka_India_2.jpg" +byline = "CC BY-SA 4.0 Ms Sarah Welch" + +[[mediums.works]] +name = "Charminar" +year = 1591 +location = "Hyderabad, India" +wiki = "https://en.wikipedia.org/wiki/Charminar" +[[mediums.works.figures]] +file = "Charminar-Pride_of_Hyderabad.jpg" +byline = "CC BY-SA 3.0 Gopikrishna Narla" +[[mediums.works.figures]] +file = "The_interior_view_of_Charminar.jpg" +byline = "CC BY-SA 4.0 Chinmayee Mishra" + +[[mediums.works]] +name = "Sanchi Stupa" +year = -300 +location = "Sanchi Town, India" +wiki = "https://en.wikipedia.org/wiki/Sanchi" +[[mediums.works.figures]] +file = "East_Gateway_-_Stupa_1_-_Sanchi_Hill_2013-02-21_4398.JPG" +byline = "CC BY 3.0 Biswarup Ganguly" +[[mediums.works.figures]] +file = "Temptation_of_the_Buddha_with_Mara_and_his_daughters_and_the_demons_of_Mara_fleeing_Sanchi_Stupa_1_Northern_Gateway.jpg" +byline = "CC BY-SA 3.0 Biswarup Ganguly" + +[[mediums.works]] +name = "Golden Temple" +year = 1581 +location = "Amritsar, India" +wiki = "https://en.wikipedia.org/wiki/Golden_Temple" +[[mediums.works.figures]] +file = "Golden_Temple_nighttime.jpg" +byline = "CC BY-SA 4.0 Marsmux" +[[mediums.works.figures]] +file = "Darbar_Sahib_interior_26_September_2018.jpg" +byline = "CC BY-SA 4.0 Amritpal Singh Mann" + +[[mediums.works]] +name = "Songjiang Square Pagoda" +year = 1068 +location = "Songjiang, China" +wiki = "https://en.wikipedia.org/wiki/Songjiang_Square_Pagoda" +[[mediums.works.figures]] +file = "Pagoda_at_Xingshengjiao_Temple.jpg" +byline = "CC BY-SA 4.0 Humanclose" + +[[mediums.works]] +name = "Great Mosque of Xi’an" +year = 742 +location = "Xi’an, China" +wiki = "https://en.wikipedia.org/wiki/Great_Mosque_of_Xi%27an" +[[mediums.works.figures]] +file = "Xian_Mosque3.jpg" +byline = "CC BY-SA 4.0 Tea4tori" +[[mediums.works.figures]] +file = "Great_Mosque_of_Xi%27an_pavilion_ceiling.JPG" +byline = "CC BY 3.0 BrokenSphere" +[[mediums.works.figures]] +file = "Chinese-style_minaret_of_the_Great_Mosque.jpg" +byline = "CC BY-SA 3.0 Mr. Tickle" + +[[mediums]] +tag = "LyricPoetry" +label = "Lyric poetry" +description = "Sylvan historian, who canst thus express?" +disabled = true + +[[mediums]] +tag = "OperaticAria" +label = "Operatic aria" +description = "Aaaah! Je ris…" +disabled = true diff --git a/static/style.css b/static/style.css new file mode 100644 index 0000000..321d507 --- /dev/null +++ b/static/style.css @@ -0,0 +1,100 @@ +@font-face { + font-family: EBGaramond; + src: url(/static/EBGaramond-VariableFont_wght.ttf) format('woff2-variations'); + font-style: normal; +} + +@font-face { + font-family: EBGaramond; + src: url(/static/EBGaramond-Italic-VariableFont_wght.ttf) format('woff2-variations'); + font-style: italic; +} + +body { + background: #fdf3f3; + color: DarkSlateGrey; + font-family: EBGaramond, serif; + font-size: large; +} + +a { + color: #1eaedb; +} + +a:hover { + color: #0e99c4; +} + +.container { + margin: 1em; +} + +.row { + margin-bottom: 1em; +} + +.domain-name, .title { + letter-spacing: -1.5px; +} + +ul { + margin-top: 2px; + margin-bottom: 0; + padding-left: 0; +} + +figure { + margin: 0px; + display: inline-block; +} + +figcaption { + font-family: sans-serif; + font-size: small; + margin-top: -7px; +} + +img { + width: 85%; + max-width: 1200px; + padding: 5px; +} + +form { + padding: 10px; +} + +.work { + vertical-align: top; + text-align: center; +} + +.subwork { + overflow-x: scroll; + overflow-y: hidden; + white-space: nowrap; +} + +td, th { + border-bottom: 1px black solid; + border-bottom: 1px black solid; + padding: 4px; +} + +.narrow { + max-width: 31em; +} + +fieldset { + margin-bottom: 10px; +} + +p { + margin-top: .3em; + margin-bottom: .3em; +} + +.sep { + margin-left: 3px; + margin-right: 3px; +} diff --git a/urlescape b/urlescape new file mode 100755 index 0000000..413e7e3 --- /dev/null +++ b/urlescape @@ -0,0 +1,8 @@ +#!/usr/bin/env bash +for f in ./static/assets/*; do + g="$(echo "$f" | sed "s@+@ @g;s@%@\\\\x@g" | xargs -0 printf "%b")" + if [ "$f" != "$g" ]; then + echo mv "$f" "$g" + mv "$f" "$g" + fi +done |