76 lines
2.3 KiB
Haskell
76 lines
2.3 KiB
Haskell
|
module Publications where
|
||
|
|
||
|
import Prelude
|
||
|
import Control.Applicative ((<|>))
|
||
|
import Data.Aeson
|
||
|
import Data.Aeson.Types
|
||
|
import Data.Text (Text)
|
||
|
import Data.Text.Lazy.Builder
|
||
|
import Data.Binary (Binary)
|
||
|
import GHC.Generics (Generic)
|
||
|
|
||
|
import Data.Text.Lazy qualified as LT
|
||
|
|
||
|
|
||
|
-- Some structured definitions for bibliography.
|
||
|
-- It's not *strictly* necessery per se, but this allows detecting formatting
|
||
|
-- errors at build-time rather than produce incorrect HTML.
|
||
|
|
||
|
|
||
|
-- publication authors may have a website and orcid
|
||
|
data Author = Author
|
||
|
{ name :: Text
|
||
|
, url :: Maybe Text
|
||
|
, orcid :: Maybe Text
|
||
|
} deriving (Eq, Show, Generic, Binary, ToJSON)
|
||
|
|
||
|
instance FromJSON Author where
|
||
|
parseJSON o = withObject "Author info" authorInfo o <|> withText "Author name" authorName o
|
||
|
where authorInfo :: Object -> Parser Author
|
||
|
authorInfo v =
|
||
|
Author <$> v .: "name"
|
||
|
<*> v .:? "url"
|
||
|
<*> v .:? "orcid"
|
||
|
|
||
|
authorName :: Text -> Parser Author
|
||
|
authorName s = pure $ Author s Nothing Nothing
|
||
|
|
||
|
|
||
|
-- wrapper around list of authors, with a custom ToJSON instance that produces a nicely separated list
|
||
|
newtype Authors = Authors [Author] deriving newtype (Eq, Binary, FromJSON)
|
||
|
|
||
|
instance ToJSON Authors where
|
||
|
toJSON (Authors authors) =
|
||
|
String $ LT.toStrict $ toLazyText $ joinSmart (fmap renderAuthor authors)
|
||
|
where renderAuthor :: Author -> Builder
|
||
|
renderAuthor (Author name Nothing orcid) = fromText name
|
||
|
renderAuthor (Author name (Just url) orcid) =
|
||
|
"<a href=\"" <> fromText url <> "\">" <> fromText name <> "</a>"
|
||
|
|
||
|
joinSmart :: [Builder] -> Builder
|
||
|
joinSmart chunks = case chunks of
|
||
|
[] -> mempty
|
||
|
[one] -> one
|
||
|
[one, two] -> one <> " and " <> two
|
||
|
first:rest -> first <> ", " <> joinSmart rest
|
||
|
|
||
|
-- publication venue
|
||
|
data Venue = Venue
|
||
|
{ name :: Text
|
||
|
, url :: Text
|
||
|
} deriving (Eq, Generic, Binary, FromJSON, ToJSON)
|
||
|
|
||
|
data Publication = Publication
|
||
|
{ title :: Text
|
||
|
, slug :: Text
|
||
|
, authors :: Authors
|
||
|
, file :: Maybe Text
|
||
|
, doi :: Maybe Text
|
||
|
, venue :: Venue
|
||
|
} deriving (Eq, Generic, Binary, FromJSON, ToJSON)
|
||
|
|
||
|
data PubGroup = PubGroup
|
||
|
{ year :: Text
|
||
|
, pubs :: [Publication]
|
||
|
} deriving (Generic, Eq, Binary, FromJSON, ToJSON)
|