-- | Standard code to make a table of units.
-- First true example of a (small) recipe.
module Drasil.Sections.TableOfUnits (tOfUnitDesc, tOfUnitSIName, unitTableRef, tunit, tunit', tunitNone, tuIntro, defaultTUI) where

import Control.Lens ((^.))
import Language.Drasil
import Drasil.Sections.ReferenceMaterial(emptySectSentPlu)
import Data.Drasil.Concepts.Documentation (symbol_, description, tOfUnit)
import Drasil.DocumentLanguage.Core (TUIntro(..), RefTab(..))
import Data.Drasil.Concepts.Math (unit_)

-- | Creates the Table of Units with an "SI Name" column.
tOfUnitSIName :: IsUnit s => [s] -> LabelledContent
tOfUnitSIName :: forall s. IsUnit s => [s] -> LabelledContent
tOfUnitSIName = forall s. [Sentence] -> [s -> Sentence] -> [s] -> LabelledContent
tOfUnitHelper [forall n. NamedIdea n => n -> Sentence
atStart IdeaDict
symbol_, forall n. NamedIdea n => n -> Sentence
atStart IdeaDict
description, String -> Sentence
S String
"SI Name"]
                  [USymb -> Sentence
Sy forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall u. HasUnitSymbol u => u -> USymb
usymb, (forall s a. s -> Getting a s a -> a
^. forall c. Definition c => Lens' c Sentence
defn), forall n. NamedIdea n => n -> Sentence
phrase]

-- | Creates the Table of Units with SI name in the "Description" column.
tOfUnitDesc :: IsUnit s => [s] -> LabelledContent
tOfUnitDesc :: forall s. IsUnit s => [s] -> LabelledContent
tOfUnitDesc = forall s. [Sentence] -> [s -> Sentence] -> [s] -> LabelledContent
tOfUnitHelper [forall n. NamedIdea n => n -> Sentence
atStart IdeaDict
symbol_, forall n. NamedIdea n => n -> Sentence
atStart IdeaDict
description]
                 [USymb -> Sentence
Sy forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall u. HasUnitSymbol u => u -> USymb
usymb, \s
x -> (s
x forall s a. s -> Getting a s a -> a
^. forall c. Definition c => Lens' c Sentence
defn) Sentence -> Sentence -> Sentence
+:+ Sentence -> Sentence
sParen (forall n. NamedIdea n => n -> Sentence
phrase s
x)]

tOfUnitNone :: [UnitDefn] -> LabelledContent
tOfUnitNone :: [UnitDefn] -> LabelledContent
tOfUnitNone [] = forall s. [Sentence] -> [s -> Sentence] -> [s] -> LabelledContent
tOfUnitHelper [] [] []
tOfUnitNone [UnitDefn]
_ = forall s. [Sentence] -> [s -> Sentence] -> [s] -> LabelledContent
tOfUnitHelper [] [] []

-- | Helper for making a Table of Units.
tOfUnitHelper :: [Sentence] -> [s -> Sentence] -> [s] -> LabelledContent
tOfUnitHelper :: forall s. [Sentence] -> [s -> Sentence] -> [s] -> LabelledContent
tOfUnitHelper [Sentence]
_       [s -> Sentence]
_  [] = Reference -> RawContent -> LabelledContent
llcc Reference
unitTableRef forall a b. (a -> b) -> a -> b
$ Sentence -> RawContent
Paragraph Sentence
EmptyS
tOfUnitHelper []      [s -> Sentence]
_  [s]
_  = Reference -> RawContent -> LabelledContent
llcc Reference
unitTableRef forall a b. (a -> b) -> a -> b
$ Sentence -> RawContent
Paragraph Sentence
EmptyS
tOfUnitHelper [Sentence]
_       [] [s]
_  = Reference -> RawContent -> LabelledContent
llcc Reference
unitTableRef forall a b. (a -> b) -> a -> b
$ Sentence -> RawContent
Paragraph Sentence
EmptyS
tOfUnitHelper [Sentence]
headers [s -> Sentence]
fs [s]
u  = Reference -> RawContent -> LabelledContent
llcc Reference
unitTableRef forall a b. (a -> b) -> a -> b
$ [Sentence] -> [[Sentence]] -> Sentence -> Bool -> RawContent
Table [Sentence]
headers
  (forall a b. [a -> b] -> [a] -> [[b]]
mkTable [s -> Sentence]
fs [s]
u) (String -> Sentence
S String
"Table of Units") Bool
True

-- | Makes a reference to the Table of Units.
unitTableRef :: Reference
unitTableRef :: Reference
unitTableRef = String -> Reference
makeTabRef String
"ToU"

----- Table of units section helper functions -----

-- | Table of units constructors.
tunit, tunit', tunitNone :: [TUIntro] -> RefTab
-- | Table of units with an SI Name.
tunit :: [TUIntro] -> RefTab
tunit  [TUIntro]
t = [TUIntro] -> ([UnitDefn] -> LabelledContent) -> RefTab
TUnits' [TUIntro]
t forall s. IsUnit s => [s] -> LabelledContent
tOfUnitSIName
-- | Table of units with SI name in the description column.
tunit' :: [TUIntro] -> RefTab
tunit' [TUIntro]
t = [TUIntro] -> ([UnitDefn] -> LabelledContent) -> RefTab
TUnits' [TUIntro]
t forall s. IsUnit s => [s] -> LabelledContent
tOfUnitDesc
-- | Table of units with SI name in the description column.
tunitNone :: [TUIntro] -> RefTab
tunitNone [TUIntro]
t = [TUIntro] -> ([UnitDefn] -> LabelledContent) -> RefTab
TUnits' [TUIntro]
t [UnitDefn] -> LabelledContent
tOfUnitNone

-- | Table of units introduction builder. Used by 'mkRefSec'.
tuIntro :: [TUIntro] -> Contents
tuIntro :: [TUIntro] -> Contents
tuIntro [] = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall n. NamedIdea n => [n] -> Sentence
emptySectSentPlu [ConceptChunk
unit_]
tuIntro [TUIntro]
x = Sentence -> Contents
mkParagraph forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Sentence -> Sentence -> Sentence
(+:+) forall b c a. (b -> c) -> (a -> b) -> a -> c
. TUIntro -> Sentence
tuI) Sentence
EmptyS [TUIntro]
x

-- | Table of units introduction writer. Translates a 'TUIntro' to a 'Sentence'.
tuI :: TUIntro -> Sentence
tuI :: TUIntro -> Sentence
tuI TUIntro
System  =
  String -> Sentence
S String
"The unit system used throughout is SI (Système International d'Unités)."
tuI TUIntro
TUPurpose =
  String -> Sentence
S String
"For each unit" Sentence -> Sentence -> Sentence
`sC` String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+ forall r.
(HasUID r, HasRefAddress r, HasShortName r) =>
r -> Sentence -> Sentence
namedRef Reference
unitTableRef (forall n. NamedIdea n => n -> Sentence
titleize' IdeaDict
tOfUnit) Sentence -> Sentence -> Sentence
+:+
    String -> Sentence
S String
"lists" Sentence -> Sentence -> Sentence
+:+. SepType -> FoldType -> [Sentence] -> Sentence
foldlList SepType
Comma FoldType
List [String -> Sentence
S String
"the" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
symbol_,
    String -> Sentence
S String
"a" Sentence -> Sentence -> Sentence
+:+ forall n. NamedIdea n => n -> Sentence
phrase IdeaDict
description, String -> Sentence
S String
"the SI name"]
tuI TUIntro
Derived =
  String -> Sentence
S String
"In addition to the basic units, several derived units are also used."

-- | Default table of units intro that contains the system, derivation, and purpose.
defaultTUI :: [TUIntro]
defaultTUI :: [TUIntro]
defaultTUI = [TUIntro
System, TUIntro
Derived, TUIntro
TUPurpose]