{- |

Open Graph metadata, as described at <https://ogp.me/>.  This
implementation supports the following properties:

+------------------+----------------------------------------------------+
| @og:type@        | __Hardcoded__ value @"article"@                    |
+------------------+----------------------------------------------------+
| @og:url@         | __Required__ concatenation of @root@ and @url@     |
|                  | context fields, both of which are required.        |
+------------------+----------------------------------------------------+
| @og:title@       | __Required__ title of article, from @title@ field. |
+------------------+----------------------------------------------------+
| @og:description@ | __Optional__ brief description taken from context  |
|                  | field @og-description@, if set.                    |
+------------------+----------------------------------------------------+
| @og:image@       | __Optional__ image URL taken from context          |
|                  | field @og-image@, if set.                          |
+------------------+----------------------------------------------------+

To use, add 'openGraphField' to the template context:

@
let
  context = 'defaultContext' <> …
  postContext = context <> 'openGraphField' "opengraph" context
@

and update the template:

@
\<head>
  \<title>$title$</title>
  \<link rel="stylesheet" type="text\/css" href="\/css\/default.css" />
  $if(opengraph)$$opengraph$$endif$
\</head>
@

See also "Hakyll.Web.Meta.TwitterCard".

-}
module Hakyll.Web.Meta.OpenGraph
  ( openGraphField
  ) where

import Hakyll.Core.Compiler
import Hakyll.Core.Item
import Hakyll.Web.Template
import Hakyll.Web.Template.Context

openGraphField :: String -> Context String -> Context String
openGraphField :: String -> Context String -> Context String
openGraphField String
k Context String
ctx = String
-> ([String] -> Item String -> Compiler String) -> Context String
forall a.
String -> ([String] -> Item a -> Compiler String) -> Context a
functionField String
k (([String] -> Item String -> Compiler String) -> Context String)
-> ([String] -> Item String -> Compiler String) -> Context String
forall a b. (a -> b) -> a -> b
$ \[String]
_args Item String
i -> do
  Template
template <- Compiler Template
openGraphTemplate
  Item String -> String
forall a. Item a -> a
itemBody (Item String -> String)
-> Compiler (Item String) -> Compiler String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Template -> Context String -> Item String -> Compiler (Item String)
forall a. Template -> Context a -> Item a -> Compiler (Item String)
applyTemplate Template
template Context String
ctx Item String
i

openGraphTemplate :: Compiler Template
openGraphTemplate :: Compiler Template
openGraphTemplate = do
  String -> Compiler (Item String)
forall a. a -> Compiler (Item a)
makeItem String
openGraphTemplateString Compiler (Item String)
-> (Item String -> Compiler Template) -> Compiler Template
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Item String -> Compiler Template
compileTemplateItem

openGraphTemplateString :: String
openGraphTemplateString :: String
openGraphTemplateString =
  String
"<meta property=\"og:type\" content=\"article\" />\
  \<meta property=\"og:url\" content=\"$root$$url$\" />\
  \<meta property=\"og:title\" content=\"$title$\" />\
  \$if(og-description)$\
  \<meta property=\"og:description\" content=\"$og-description$\" />\
  \$endif$\
  \$if(og-image)$\
  \<meta property=\"og:image\" content=\"$og-image$\" />\
  \$endif$\
  \"