----------------------------------------------------------------------
--
-- Module      : layout and flags  takes data from the settinsgN.yaml file (metaPage deals with the md file YAML header)
----------------------------------------------------------------------
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
-- {-# LANGUAGE TypeSynonymInstances  #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

{- | the defintion for a layout and a flags type
  which carry info from the command line and the siteHeader file
 the defaults for flags are set up for testing  are overridden
 the defaults for layout must correspond to what is set in the test siteHeader file.
 layout defaults are used in testing

 content dirs are those, which have *.md files
-}
module Foundational.SettingsPage
    (module Foundational.SettingsPage
    , def 
    ) where

import UniformBase
import Data.Default.Class ( Default(def) ) -- to define a default class for siteLayout 
import Uniform.Json ( FromJSON, ToJSON )

import Path (parent)
progName, progTitle :: Text
progName :: Text
progName = Text
"daino"  
progTitle :: Text
progTitle = Text
"constructing a static site generator" :: Text

settingsFileName :: Path Rel File
-- ^ the yaml file in which the siteHeader are fixec
settingsFileName :: Path Rel File
settingsFileName = FilePath -> Path Rel File
makeRelFile FilePath
"settings3" -- the yaml file

-- | the siteHeader file with all fields 
data Settings = Settings
    { Settings -> SiteLayout
siteLayout :: SiteLayout 
    , Settings -> Int
localhostPort :: Int 
    , Settings -> Text
settingsAuthor :: Text 
    , Settings -> Text
settingsDate :: Text -- should be UTC 
    , Settings -> SiteHeader
siteHeader :: SiteHeader 
    , Settings -> MenuItems
menuitems :: MenuItems
    -- , today :: Text
    } deriving (Int -> Settings -> ShowS
[Settings] -> ShowS
Settings -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [Settings] -> ShowS
$cshowList :: [Settings] -> ShowS
show :: Settings -> FilePath
$cshow :: Settings -> FilePath
showsPrec :: Int -> Settings -> ShowS
$cshowsPrec :: Int -> Settings -> ShowS
Show, ReadPrec [Settings]
ReadPrec Settings
Int -> ReadS Settings
ReadS [Settings]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Settings]
$creadListPrec :: ReadPrec [Settings]
readPrec :: ReadPrec Settings
$creadPrec :: ReadPrec Settings
readList :: ReadS [Settings]
$creadList :: ReadS [Settings]
readsPrec :: Int -> ReadS Settings
$creadsPrec :: Int -> ReadS Settings
Read, Eq Settings
Settings -> Settings -> Bool
Settings -> Settings -> Ordering
Settings -> Settings -> Settings
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Settings -> Settings -> Settings
$cmin :: Settings -> Settings -> Settings
max :: Settings -> Settings -> Settings
$cmax :: Settings -> Settings -> Settings
>= :: Settings -> Settings -> Bool
$c>= :: Settings -> Settings -> Bool
> :: Settings -> Settings -> Bool
$c> :: Settings -> Settings -> Bool
<= :: Settings -> Settings -> Bool
$c<= :: Settings -> Settings -> Bool
< :: Settings -> Settings -> Bool
$c< :: Settings -> Settings -> Bool
compare :: Settings -> Settings -> Ordering
$ccompare :: Settings -> Settings -> Ordering
Ord, Settings -> Settings -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Settings -> Settings -> Bool
$c/= :: Settings -> Settings -> Bool
== :: Settings -> Settings -> Bool
$c== :: Settings -> Settings -> Bool
Eq, forall x. Rep Settings x -> Settings
forall x. Settings -> Rep Settings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Settings x -> Settings
$cfrom :: forall x. Settings -> Rep Settings x
Generic, Settings
Eq Settings => Settings -> Bool
forall z.
z -> (Eq z => z -> Bool) -> (Eq z => z -> Bool) -> Zeros z
notZero :: Eq Settings => Settings -> Bool
$cnotZero :: Eq Settings => Settings -> Bool
isZero :: Eq Settings => Settings -> Bool
$cisZero :: Eq Settings => Settings -> Bool
zero :: Settings
$czero :: Settings
Zeros)

instance ToJSON Settings
instance FromJSON Settings

data SiteHeader = SiteHeader 
    { SiteHeader -> FilePath
sitename :: FilePath 
    , SiteHeader -> Text
byline :: Text 
    ,  :: FilePath 
    , SiteHeader -> Text
bannerCaption :: Text 
    } deriving (Int -> SiteHeader -> ShowS
[SiteHeader] -> ShowS
SiteHeader -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SiteHeader] -> ShowS
$cshowList :: [SiteHeader] -> ShowS
show :: SiteHeader -> FilePath
$cshow :: SiteHeader -> FilePath
showsPrec :: Int -> SiteHeader -> ShowS
$cshowsPrec :: Int -> SiteHeader -> ShowS
Show, ReadPrec [SiteHeader]
ReadPrec SiteHeader
Int -> ReadS SiteHeader
ReadS [SiteHeader]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SiteHeader]
$creadListPrec :: ReadPrec [SiteHeader]
readPrec :: ReadPrec SiteHeader
$creadPrec :: ReadPrec SiteHeader
readList :: ReadS [SiteHeader]
$creadList :: ReadS [SiteHeader]
readsPrec :: Int -> ReadS SiteHeader
$creadsPrec :: Int -> ReadS SiteHeader
Read, Eq SiteHeader
SiteHeader -> SiteHeader -> Bool
SiteHeader -> SiteHeader -> Ordering
SiteHeader -> SiteHeader -> SiteHeader
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SiteHeader -> SiteHeader -> SiteHeader
$cmin :: SiteHeader -> SiteHeader -> SiteHeader
max :: SiteHeader -> SiteHeader -> SiteHeader
$cmax :: SiteHeader -> SiteHeader -> SiteHeader
>= :: SiteHeader -> SiteHeader -> Bool
$c>= :: SiteHeader -> SiteHeader -> Bool
> :: SiteHeader -> SiteHeader -> Bool
$c> :: SiteHeader -> SiteHeader -> Bool
<= :: SiteHeader -> SiteHeader -> Bool
$c<= :: SiteHeader -> SiteHeader -> Bool
< :: SiteHeader -> SiteHeader -> Bool
$c< :: SiteHeader -> SiteHeader -> Bool
compare :: SiteHeader -> SiteHeader -> Ordering
$ccompare :: SiteHeader -> SiteHeader -> Ordering
Ord, SiteHeader -> SiteHeader -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SiteHeader -> SiteHeader -> Bool
$c/= :: SiteHeader -> SiteHeader -> Bool
== :: SiteHeader -> SiteHeader -> Bool
$c== :: SiteHeader -> SiteHeader -> Bool
Eq, forall x. Rep SiteHeader x -> SiteHeader
forall x. SiteHeader -> Rep SiteHeader x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SiteHeader x -> SiteHeader
$cfrom :: forall x. SiteHeader -> Rep SiteHeader x
Generic, SiteHeader
Eq SiteHeader => SiteHeader -> Bool
forall z.
z -> (Eq z => z -> Bool) -> (Eq z => z -> Bool) -> Zeros z
notZero :: Eq SiteHeader => SiteHeader -> Bool
$cnotZero :: Eq SiteHeader => SiteHeader -> Bool
isZero :: Eq SiteHeader => SiteHeader -> Bool
$cisZero :: Eq SiteHeader => SiteHeader -> Bool
zero :: SiteHeader
$czero :: SiteHeader
Zeros)
instance ToJSON SiteHeader
instance FromJSON SiteHeader

newtype MenuItems = MenuItems {MenuItems -> [MenuItem]
menuNav:: [MenuItem]
                            -- , menuB:: Text
                            } deriving (Int -> MenuItems -> ShowS
[MenuItems] -> ShowS
MenuItems -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [MenuItems] -> ShowS
$cshowList :: [MenuItems] -> ShowS
show :: MenuItems -> FilePath
$cshow :: MenuItems -> FilePath
showsPrec :: Int -> MenuItems -> ShowS
$cshowsPrec :: Int -> MenuItems -> ShowS
Show, ReadPrec [MenuItems]
ReadPrec MenuItems
Int -> ReadS MenuItems
ReadS [MenuItems]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MenuItems]
$creadListPrec :: ReadPrec [MenuItems]
readPrec :: ReadPrec MenuItems
$creadPrec :: ReadPrec MenuItems
readList :: ReadS [MenuItems]
$creadList :: ReadS [MenuItems]
readsPrec :: Int -> ReadS MenuItems
$creadsPrec :: Int -> ReadS MenuItems
Read, Eq MenuItems
MenuItems -> MenuItems -> Bool
MenuItems -> MenuItems -> Ordering
MenuItems -> MenuItems -> MenuItems
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MenuItems -> MenuItems -> MenuItems
$cmin :: MenuItems -> MenuItems -> MenuItems
max :: MenuItems -> MenuItems -> MenuItems
$cmax :: MenuItems -> MenuItems -> MenuItems
>= :: MenuItems -> MenuItems -> Bool
$c>= :: MenuItems -> MenuItems -> Bool
> :: MenuItems -> MenuItems -> Bool
$c> :: MenuItems -> MenuItems -> Bool
<= :: MenuItems -> MenuItems -> Bool
$c<= :: MenuItems -> MenuItems -> Bool
< :: MenuItems -> MenuItems -> Bool
$c< :: MenuItems -> MenuItems -> Bool
compare :: MenuItems -> MenuItems -> Ordering
$ccompare :: MenuItems -> MenuItems -> Ordering
Ord, MenuItems -> MenuItems -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MenuItems -> MenuItems -> Bool
$c/= :: MenuItems -> MenuItems -> Bool
== :: MenuItems -> MenuItems -> Bool
$c== :: MenuItems -> MenuItems -> Bool
Eq, forall x. Rep MenuItems x -> MenuItems
forall x. MenuItems -> Rep MenuItems x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MenuItems x -> MenuItems
$cfrom :: forall x. MenuItems -> Rep MenuItems x
Generic, MenuItems
Eq MenuItems => MenuItems -> Bool
forall z.
z -> (Eq z => z -> Bool) -> (Eq z => z -> Bool) -> Zeros z
notZero :: Eq MenuItems => MenuItems -> Bool
$cnotZero :: Eq MenuItems => MenuItems -> Bool
isZero :: Eq MenuItems => MenuItems -> Bool
$cisZero :: Eq MenuItems => MenuItems -> Bool
zero :: MenuItems
$czero :: MenuItems
Zeros)
instance ToJSON MenuItems 
instance FromJSON MenuItems 

data MenuItem = MenuItem  
    { MenuItem -> FilePath
navlink :: FilePath 
    , MenuItem -> Text
navtext :: Text
    -- , navpdf :: Text  -- for the link to the pdf 
    -- not a good idead to put here
    } deriving (Int -> MenuItem -> ShowS
[MenuItem] -> ShowS
MenuItem -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [MenuItem] -> ShowS
$cshowList :: [MenuItem] -> ShowS
show :: MenuItem -> FilePath
$cshow :: MenuItem -> FilePath
showsPrec :: Int -> MenuItem -> ShowS
$cshowsPrec :: Int -> MenuItem -> ShowS
Show, ReadPrec [MenuItem]
ReadPrec MenuItem
Int -> ReadS MenuItem
ReadS [MenuItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MenuItem]
$creadListPrec :: ReadPrec [MenuItem]
readPrec :: ReadPrec MenuItem
$creadPrec :: ReadPrec MenuItem
readList :: ReadS [MenuItem]
$creadList :: ReadS [MenuItem]
readsPrec :: Int -> ReadS MenuItem
$creadsPrec :: Int -> ReadS MenuItem
Read, Eq MenuItem
MenuItem -> MenuItem -> Bool
MenuItem -> MenuItem -> Ordering
MenuItem -> MenuItem -> MenuItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MenuItem -> MenuItem -> MenuItem
$cmin :: MenuItem -> MenuItem -> MenuItem
max :: MenuItem -> MenuItem -> MenuItem
$cmax :: MenuItem -> MenuItem -> MenuItem
>= :: MenuItem -> MenuItem -> Bool
$c>= :: MenuItem -> MenuItem -> Bool
> :: MenuItem -> MenuItem -> Bool
$c> :: MenuItem -> MenuItem -> Bool
<= :: MenuItem -> MenuItem -> Bool
$c<= :: MenuItem -> MenuItem -> Bool
< :: MenuItem -> MenuItem -> Bool
$c< :: MenuItem -> MenuItem -> Bool
compare :: MenuItem -> MenuItem -> Ordering
$ccompare :: MenuItem -> MenuItem -> Ordering
Ord, MenuItem -> MenuItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MenuItem -> MenuItem -> Bool
$c/= :: MenuItem -> MenuItem -> Bool
== :: MenuItem -> MenuItem -> Bool
$c== :: MenuItem -> MenuItem -> Bool
Eq, forall x. Rep MenuItem x -> MenuItem
forall x. MenuItem -> Rep MenuItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MenuItem x -> MenuItem
$cfrom :: forall x. MenuItem -> Rep MenuItem x
Generic, MenuItem
Eq MenuItem => MenuItem -> Bool
forall z.
z -> (Eq z => z -> Bool) -> (Eq z => z -> Bool) -> Zeros z
notZero :: Eq MenuItem => MenuItem -> Bool
$cnotZero :: Eq MenuItem => MenuItem -> Bool
isZero :: Eq MenuItem => MenuItem -> Bool
$cisZero :: Eq MenuItem => MenuItem -> Bool
zero :: MenuItem
$czero :: MenuItem
Zeros)
instance ToJSON MenuItem
instance FromJSON MenuItem

data SiteLayout = SiteLayout
    { -- | the place of the  theme files (includes templates)
      SiteLayout -> Path Abs Dir
themeDir :: Path Abs Dir
    , -- | where the content is originally (includes resources)
      SiteLayout -> Path Abs Dir
doughDir :: Path Abs Dir
    , -- | the webroot, the dir with all the produced files
      SiteLayout -> Path Abs Dir
bakedDir :: Path Abs Dir
    , SiteLayout -> Path Rel File
masterTemplateFile :: Path Rel File  -- for html
    , SiteLayout -> Path Rel File
texTemplateFile :: Path Rel File   -- for latex 
    , SiteLayout -> Text
doNotBake :: Text 
    -- todo probably not used
    , SiteLayout -> [Text]
blogAuthorToSuppress :: [Text]
    , SiteLayout -> Text
defaultAuthor :: Text
    , SiteLayout -> Path Abs File
replaceErlaubtFile :: Path Abs File
    -- the list of permitted (not to replace)
    
    -- , defaultBibliography:: Text
    -- cannot be defaulted, value must be read by pandoc 
    }
    deriving (Int -> SiteLayout -> ShowS
[SiteLayout] -> ShowS
SiteLayout -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [SiteLayout] -> ShowS
$cshowList :: [SiteLayout] -> ShowS
show :: SiteLayout -> FilePath
$cshow :: SiteLayout -> FilePath
showsPrec :: Int -> SiteLayout -> ShowS
$cshowsPrec :: Int -> SiteLayout -> ShowS
Show, ReadPrec [SiteLayout]
ReadPrec SiteLayout
Int -> ReadS SiteLayout
ReadS [SiteLayout]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SiteLayout]
$creadListPrec :: ReadPrec [SiteLayout]
readPrec :: ReadPrec SiteLayout
$creadPrec :: ReadPrec SiteLayout
readList :: ReadS [SiteLayout]
$creadList :: ReadS [SiteLayout]
readsPrec :: Int -> ReadS SiteLayout
$creadsPrec :: Int -> ReadS SiteLayout
Read, Eq SiteLayout
SiteLayout -> SiteLayout -> Bool
SiteLayout -> SiteLayout -> Ordering
SiteLayout -> SiteLayout -> SiteLayout
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SiteLayout -> SiteLayout -> SiteLayout
$cmin :: SiteLayout -> SiteLayout -> SiteLayout
max :: SiteLayout -> SiteLayout -> SiteLayout
$cmax :: SiteLayout -> SiteLayout -> SiteLayout
>= :: SiteLayout -> SiteLayout -> Bool
$c>= :: SiteLayout -> SiteLayout -> Bool
> :: SiteLayout -> SiteLayout -> Bool
$c> :: SiteLayout -> SiteLayout -> Bool
<= :: SiteLayout -> SiteLayout -> Bool
$c<= :: SiteLayout -> SiteLayout -> Bool
< :: SiteLayout -> SiteLayout -> Bool
$c< :: SiteLayout -> SiteLayout -> Bool
compare :: SiteLayout -> SiteLayout -> Ordering
$ccompare :: SiteLayout -> SiteLayout -> Ordering
Ord, SiteLayout -> SiteLayout -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SiteLayout -> SiteLayout -> Bool
$c/= :: SiteLayout -> SiteLayout -> Bool
== :: SiteLayout -> SiteLayout -> Bool
$c== :: SiteLayout -> SiteLayout -> Bool
Eq, forall x. Rep SiteLayout x -> SiteLayout
forall x. SiteLayout -> Rep SiteLayout x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SiteLayout x -> SiteLayout
$cfrom :: forall x. SiteLayout -> Rep SiteLayout x
Generic, SiteLayout
Eq SiteLayout => SiteLayout -> Bool
forall z.
z -> (Eq z => z -> Bool) -> (Eq z => z -> Bool) -> Zeros z
notZero :: Eq SiteLayout => SiteLayout -> Bool
$cnotZero :: Eq SiteLayout => SiteLayout -> Bool
isZero :: Eq SiteLayout => SiteLayout -> Bool
$cisZero :: Eq SiteLayout => SiteLayout -> Bool
zero :: SiteLayout
$czero :: SiteLayout
Zeros)
instance ToJSON SiteLayout
instance FromJSON SiteLayout
 

sourceDirTestDocs :: Path Abs Dir
sourceDirTestDocs :: Path Abs Dir
sourceDirTestDocs = FilePath -> Path Abs Dir
makeAbsDir FilePath
"/home/frank/daino/docs/"

sourceDirTestSite :: Path Abs Dir
sourceDirTestSite :: Path Abs Dir
sourceDirTestSite = Path Abs Dir
sourceDirTestDocs forall fp file.
Filenames3 fp file =>
fp -> file -> FileResultT fp file
</> (FilePath -> Path Rel Dir
makeRelDir FilePath
"site")
-- ^ the dir with the source for the test site

layoutDefaults :: Path Abs Dir -> Path Abs Dir ->  SiteLayout
-- used for finding the test cases
-- must correspond to the settings3.yaml in source code repository
-- fix this later for use in testing todo 
layoutDefaults :: Path Abs Dir -> Path Abs Dir -> SiteLayout
layoutDefaults Path Abs Dir
dough4test Path Abs Dir
homeDir =
    forall z. Zeros z => z
zero -- SiteLayout
        { doughDir :: Path Abs Dir
doughDir = Path Abs Dir
dough4test
        , bakedDir :: Path Abs Dir
bakedDir = Path Abs Dir
homeDir forall fp file.
Filenames3 fp file =>
fp -> file -> FileResultT fp file
</> FilePath -> Path Rel Dir
makeRelDir FilePath
"bakedTestSite" :: Path Abs Dir
        ,  themeDir :: Path Abs Dir
themeDir = (forall b t. Path b t -> Path b Dir
parent (forall b t. Path b t -> Path b Dir
parent Path Abs Dir
dough4test)) forall fp file.
Filenames3 fp file =>
fp -> file -> FileResultT fp file
</> FilePath -> Path Rel Dir
makeRelDir FilePath
"theme"
 
        ,  masterTemplateFile :: Path Rel File
masterTemplateFile = FilePath -> Path Rel File
makeRelFile FilePath
"master7tufte.dtpl"
        , texTemplateFile :: Path Rel File
texTemplateFile = FilePath -> Path Rel File
makeRelFile FilePath
"resources/theme/templates/latex7.dtpl"
        ,  doNotBake :: Text
doNotBake = Text
"DNB"
        -- included in filenames (and directories) to exclude from bake process
        , blogAuthorToSuppress :: [Text]
blogAuthorToSuppress = []
        , defaultAuthor :: Text
defaultAuthor = Text
"AOS"
        , replaceErlaubtFile :: Path Abs File
replaceErlaubtFile = FilePath -> Path Abs File
makeAbsFile FilePath
"/home/frank/Workspace11/replaceUmlaut/nichtUmlaute.txt"
        -- , defaultBibliography = "resources/BibTexLatex.bib"
        }

-- instance Default SiteLayout where 
--         def = layoutDefaults

-- notDNB :: SiteLayout -> FilePath -> Bool 
-- notDNB siteLayout = not . isInfixOf' (t2s $ doNotPublish siteLayout)

resourcesName :: FilePath
resourcesName =  FilePath
"resources"
templatesName :: FilePath
templatesName = FilePath
"templates"
themeName :: FilePath
themeName = FilePath
"theme"

templatesDir :: SiteLayout -> Path Abs Dir
templatesDir :: SiteLayout -> Path Abs Dir
templatesDir SiteLayout
layout = SiteLayout -> Path Abs Dir
themeDir SiteLayout
layout forall fp file.
Filenames3 fp file =>
fp -> file -> FileResultT fp file
`addFileName` (FilePath -> Path Rel Dir
makeRelDir FilePath
templatesName)

blankAuthorName :: [Text] -> Text -> Text 
-- suppress/oppress author name, if the author name is the same as one in the first arg (AUF, Andrew U..) then set it to empty else copy 
-- goal is to avoid to have each page say the obvious "author XX"
blankAuthorName :: [Text] -> Text -> Text
blankAuthorName [Text]
names Text
current = 
    if Text
current forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
names 
        then forall z. Zeros z => z
zero 
        else Text
current