Skip to content

Commit

Permalink
Implemented FoldType to facilitate merge of functions - glassBR examp…
Browse files Browse the repository at this point in the history
…le broken until SepType is implemented
  • Loading branch information
samm82 committed Jul 24, 2018
1 parent 0bc8c9c commit 2496e14
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 12 deletions.
23 changes: 14 additions & 9 deletions code/drasil-data/Data/Drasil/SentenceStructures.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
module Data.Drasil.SentenceStructures
( foldlSent, foldlSent_, foldlSentCol, foldlsC, foldlList, foldlInlineList
( foldlSent, foldlSent_, foldlSentCol, foldlsC, foldlList, foldlInlineList, makeList
, sAnd, andIts, andThe, sAre, sIn, sVersus
, sIs, isThe, sOf, sOr, ofThe, ofThe'
, ofGiv, ofGiv'
Expand All @@ -15,7 +15,7 @@ module Data.Drasil.SentenceStructures
, fmtPhys, fmtSfwr, typUncr
, mkTableFromColumns
, acroA, acroGD, acroGS, acroIM, acroLC, acroPS, acroR, acroT
, EnumType(..), WrapType(..)
, EnumType(..), WrapType(..), FoldType(..)
) where

import Language.Drasil
Expand Down Expand Up @@ -68,10 +68,11 @@ foldlOptions lst = foldle1 sC (\a b -> a `sC` S "or" +:+ b) lst

data EnumType = Numb | Upper | Lower
data WrapType = Parens | Paren | Period
data FoldType = List | Options deriving (Eq)

-- | creates an list of elements with "enumerators" in "wrappers", separated by a sep, and ending with "and"
foldlInlineList :: EnumType -> WrapType -> Sentence -> [Sentence] -> Sentence
foldlInlineList e w sep lst = makeList sep $ map (\(a, b) -> a +:+ b) $ zip (numList e w $ length lst) lst
-- | creates an list of elements with "enumerators" in "wrappers", separated by a sep, and ending with "and" or "or"
foldlInlineList :: EnumType -> WrapType -> Sentence -> FoldType -> [Sentence] -> Sentence
foldlInlineList e w sep l lst = makeList sep l $ map (\(a, b) -> a +:+ b) $ zip (numList e w $ length lst) lst
where
numList :: EnumType -> WrapType -> Int -> [Sentence]
numList Numb w len = map (\x -> wrap w $ S $ show x) [1..len]
Expand All @@ -83,10 +84,14 @@ foldlInlineList e w sep lst = makeList sep $ map (\(a, b) -> a +:+ b) $ zip (num
wrap Period x = x :+: S "."

-- Helper function to foldlInlineList - not exported
makeList :: Sentence -> [Sentence] -> Sentence
makeList _ [] = EmptyS
makeList sep [a,b] = a :+: sep `sAnd` b
makeList sep (x:xs) = x :+: sep +:+ makeList sep xs
makeList :: Sentence -> FoldType -> [Sentence] -> Sentence
makeList _ _ [] = EmptyS
makeList _ l [a, b]
| l == List = a `sAnd` b
| l == Options = a `sOr` b
makeList s l lst
| l == List = foldle1 sC (\a b -> a `sC` S "and" +:+ b) lst
| l == Options = foldle1 sC (\a b -> a `sC` S "or" +:+ b) lst

{--** Combinators **--}
sAnd, andIts :: Sentence -> Sentence -> Sentence
Expand Down
7 changes: 4 additions & 3 deletions code/drasil-example/Drasil/GlassBR/Assumptions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,8 +8,9 @@ import Drasil.DocLang (cite, refA)
import Data.Drasil.Concepts.Documentation as Doc (condition, constant, practice, reference, scenario,
system, value)
import Data.Drasil.Concepts.Math (calculation, surface, shape)
import Data.Drasil.SentenceStructures (EnumType(Numb), WrapType(Parens), foldlSent, foldlSent_,
foldlOptions, foldlList, foldlInlineList, sAnd, sIn, sOf)
import Data.Drasil.SentenceStructures (EnumType(Numb), WrapType(Parens),
FoldType(List), foldlSent, foldlSent_, foldlOptions, foldlList, foldlInlineList,
sAnd, sIn, sOf)
import Data.Drasil.Concepts.PhysicalProperties (materialProprty)

import Drasil.GlassBR.Unitals ( lite, explosion, lateral, load_dur, explosion,
Expand Down Expand Up @@ -47,7 +48,7 @@ a1Desc = foldlSent [S "The standard E1300-09a for",
"laminated", "insulating"], S "glass constructions" `sOf` S "rectangular",
phrase shape, S "with continuous", phrase lateral, S "support along",
(foldlOptions $ map S ["one", "two", "three", "four"]) +:+. plural edge, S "This",
phrase practice +: S "assumes that", (foldlInlineList Numb Parens (S ";") $ map foldlSent_
phrase practice +: S "assumes that", (foldlInlineList Numb Parens (S ";") List $ map foldlSent_
[[S "the supported glass", plural edge, S "for two, three" `sAnd` S "four-sided support",
plural condition, S "are simply supported" `sAnd` S "free to slip in",
phrase plane], [S "glass supported on two sides acts as a simply supported", phrase beam],
Expand Down

1 comment on commit 2496e14

@JacquesCarette
Copy link
Owner

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

You should use pattern-matching for all clauses of makeList -- I don't like | clauses.

Please sign in to comment.