Skip to content

Commit

Permalink
Updates ListPair to ListTuple (adding RefAdd element) in Contents. Ma…
Browse files Browse the repository at this point in the history
…kes individual "items" in Contents Enumerations referable.

Adds noRefs and noRefsLT as convenience functions to make a list of ListTuples without being referable.
Updated examples accordingly.
  • Loading branch information
Mornix committed Jul 16, 2018
1 parent d8e343f commit 499239c
Show file tree
Hide file tree
Showing 11 changed files with 81 additions and 62 deletions.
23 changes: 18 additions & 5 deletions code/drasil-data/Data/Drasil/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,8 @@ module Data.Drasil.Utils
, makeTMatrix
, itemRefToSent
, refFromType
, noRefs
, noRefsLT
, makeListRef
, bulletFlat
, bulletNested
Expand Down Expand Up @@ -66,13 +68,14 @@ enumWithAbbrev start abbrev = [abbrev :+: (S $ show x) | x <- [start..]]
-- t - the title of the list
-- l - the list to be enumerated
mkEnumAbbrevList :: Integer -> Sentence -> [Sentence] -> [(Sentence, ItemType)]
mkEnumAbbrevList s t l = zip (enumWithAbbrev s t) (map Flat l)
mkEnumAbbrevList s t l = zip (enumWithAbbrev s t) $ map Flat l

-- | creates a list of references from l starting from s
-- s - start indices
-- l - list of references
mkRefsList :: Integer -> [Sentence] -> Contents
mkRefsList s l = Enumeration $ Simple $ zip (enumWithSquBrk s) (map Flat l)
mkRefsList s l = Enumeration $ Simple $ noRefsLT $ zip (enumWithSquBrk s) $
map Flat l

-- | creates a list of sentences of the form "[#]"
-- start - start indices
Expand Down Expand Up @@ -141,13 +144,13 @@ makeListRef l r = take (length l) $ repeat $ makeRef r

-- | bulletFlat applies Bullet and Flat to a list.
bulletFlat :: [Sentence] -> ListType
bulletFlat = Bullet . map Flat
bulletFlat = Bullet . noRefs . map Flat

-- | bulletNested applies Bullets and headers to a Nested ListType.
-- t - Headers of the Nested lists.
-- l - Lists of ListType.
bulletNested :: [Sentence] -> [ListType] -> ListType
bulletNested t l = Bullet . map (\(h,c) -> Nested h c) $ zip t l
bulletNested t l = Bullet . map (\(h,c) -> (Nested h c, Nothing)) $ zip t l

-- | enumBullet apply Enumeration, Bullet and Flat to a list
enumBullet ::[Sentence] -> Contents
Expand All @@ -158,7 +161,7 @@ enumBullet = Enumeration . bulletFlat
-- t - title of the list
-- l - list to be enumerated
enumSimple :: Integer -> Sentence -> [Sentence] -> Contents
enumSimple s t l = Enumeration $ Simple $ mkEnumAbbrevList s t l
enumSimple s t l = Enumeration $ Simple $ noRefsLT $ mkEnumAbbrevList s t l

-- | interweaves two lists together [[a,b,c],[d,e,f]] -> [a,d,b,e,c,f]
weave :: [[a]] -> [a]
Expand All @@ -169,6 +172,16 @@ unwrap :: (Maybe UnitDefn) -> Sentence
unwrap (Just a) = Sy (a ^. usymb)
unwrap Nothing = EmptyS

-- | noRefs converts lists of simple ItemTypes into a lists which may be used
-- in Contents but not directly referable.
noRefs :: [ItemType] -> [(ItemType, Maybe RefAdd)]
noRefs a = zip a $ repeat Nothing

-- | noRefsLT converts lists of tuples containing a title and ItemType into
-- a ListTuple which can be used with Contents but not directly referable.
noRefsLT :: [(Sentence, ItemType)] -> [ListTuple]
noRefsLT a = uncurry zip3 (unzip a) $ repeat Nothing

prodUCTbl :: [[Sentence]] -> Contents
prodUCTbl cases = Table [S "Actor", titleize input_ +:+ S "and" +:+ titleize output_]
cases
Expand Down
20 changes: 11 additions & 9 deletions code/drasil-docLang/Drasil/DocumentLanguage/Definitions.hs
Original file line number Diff line number Diff line change
Expand Up @@ -194,21 +194,23 @@ mkIMField _ _ label _ = error $ "Label " ++ show label ++ " not supported " ++

-- | Used for definitions. The first pair is the symbol of the quantity we are
-- defining.
firstPair :: InclUnits -> QDefinition -> ListPair
firstPair (IgnoreUnits) d = (P (eqSymb d), Flat (phrase d))
firstPair (IncludeUnits) d = (P (eqSymb d), Flat (phrase d +:+ sParen (unit'2Contents d)))
firstPair :: InclUnits -> QDefinition -> ListTuple
firstPair (IgnoreUnits) d = (P $ eqSymb d, Flat $ phrase d, Nothing)
firstPair (IncludeUnits) d = (P $ eqSymb d, Flat $ phrase d +:+ (sParen $
unit'2Contents d), Nothing)

-- | Used for definitions. The first pair is the symbol of the quantity we are
-- defining.
firstPair' :: InclUnits -> DataDefinition -> ListPair
firstPair' (IgnoreUnits) d = (P (eqSymb d), Flat (phrase d))
firstPair' (IncludeUnits) d = (P (eqSymb d), Flat (phrase d +:+ sParen (unit'2Contents d)))
firstPair' :: InclUnits -> DataDefinition -> ListTuple
firstPair' (IgnoreUnits) d = (P $ eqSymb d, Flat $ phrase d, Nothing)
firstPair' (IncludeUnits) d = (P $ eqSymb d, Flat $ phrase d +:+ (sParen $
unit'2Contents d), Nothing)

-- | Create the descriptions for each symbol in the relation/equation
descPairs :: (Quantity q) => InclUnits -> [q] -> [ListPair]
descPairs IgnoreUnits = map (\x -> (P (eqSymb x), Flat $ phrase x))
descPairs :: (Quantity q) => InclUnits -> [q] -> [ListTuple]
descPairs IgnoreUnits = map (\x -> (P $ eqSymb x, Flat $ phrase x, Nothing))
descPairs IncludeUnits =
map (\x -> ((P (eqSymb x)), Flat $ phrase x +:+ sParen (unit'2Contents x)))
map (\x -> (P $ eqSymb x, Flat $ phrase x +:+ (sParen $ unit'2Contents x), Nothing))
-- FIXME: Need a Units map for looking up units from variables

instance Show Field where
Expand Down
36 changes: 18 additions & 18 deletions code/drasil-example/Drasil/GlassBR/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ import Data.Drasil.SentenceStructures (acroR, sVersus, sAnd, foldlSP,
foldlsC, sOf, followA, ofThe, sIn, isThe, isExpctdToHv, sOr, underConsidertn,
tAndDWAcc, tAndDOnly, tAndDWSym, andThe)
import Data.Drasil.Software.Products (sciCompS)
import Data.Drasil.Utils (makeTMatrix, makeListRef, itemRefToSent,
import Data.Drasil.Utils (makeTMatrix, makeListRef, itemRefToSent, noRefs,
refFromType, enumSimple, enumBullet, prodUCTbl)

import Drasil.GlassBR.Assumptions (assumptionConstants, assumptionDescs,
Expand Down Expand Up @@ -204,27 +204,27 @@ functional_requirements_list, traceability_matrices_and_graphs_intro2 :: [Conten

--------------------------------------------------------------------------------
terminology_and_description_bullets :: Contents
terminology_and_description_bullets = Enumeration $ (Numeric $
map tAndDOnly termsWithDefsOnly
terminology_and_description_bullets = Enumeration $ Numeric $
noRefs $ map tAndDOnly termsWithDefsOnly
++
terminology_and_description_bullets_glTySubSec
++
terminology_and_description_bullets_loadSubSec
++
map tAndDWAcc termsWithAccDefn
++
[tAndDWSym probBreak prob_br])
[tAndDWSym probBreak prob_br]
--FIXME: merge? Needs 2 arguments because there is no instance for (SymbolForm ConceptChunk)...

terminology_and_description_bullets_glTySubSec, terminology_and_description_bullets_loadSubSec :: [ItemType]

terminology_and_description_bullets_glTySubSec = [Nested ((titleize glassTy) :+: S ":")
(Bullet $ map tAndDWAcc glassTypes)]
terminology_and_description_bullets_glTySubSec = [Nested (titleize glassTy :+: S ":") $
Bullet $ noRefs $ map tAndDWAcc glassTypes]

terminology_and_description_bullets_loadSubSec = [Nested ((at_start load) :+: S ":")
(Bullet $ map tAndDWAcc (take 2 loadTypes)
terminology_and_description_bullets_loadSubSec = [Nested (at_start load :+: S ":") $
Bullet $ noRefs $ (map tAndDWAcc $ take 2 loadTypes)
++
map tAndDOnly (drop 2 loadTypes))]
(map tAndDOnly $ drop 2 loadTypes)]

--Used in "Goal Statements" Section--
goal_statements_list :: Contents
Expand Down Expand Up @@ -562,18 +562,18 @@ testing1 :: [RelationConcept]
testing1 = [probOfBr, calOfCap, calOfDe]
--FIXME: rename or find better implementation?

functional_requirements_req6 = [(Enumeration $ Simple $ [(acroR 6, Nested (titleize output_ +:+
functional_requirements_req6 = [Enumeration $ Simple $ [(acroR 6, Nested (titleize output_ +:+
S "the following" +: plural quantity)
(Bullet $
map (\(a, d) -> Flat $ (at_start a) +:+ sParen (ch a) +:+
sParen (makeRef (reldefn d))) (zip testing testing1)
$ Bullet $ noRefs $
map (\(a, d) -> Flat $ at_start a +:+ sParen (ch a) +:+
sParen (makeRef $ reldefn d)) (zip testing testing1)
++
map (\d -> Flat $ (at_start d) +:+ sParen (ch d) +:+
sParen (makeRef (datadefn d))) functional_requirements_req6_pulledList
map (\d -> Flat $ at_start d +:+ sParen (ch d) +:+
sParen (makeRef $ datadefn d)) functional_requirements_req6_pulledList
++
[Flat $ (titleize aspectR) +:+ sParen (ch aspectR) +:+
E (aspectRWithEqn^.equat)]
))])]
[Flat $ titleize aspectR +:+ sParen (ch aspectR) +:+
E (aspectRWithEqn ^. equat)]
, Nothing)]]

{--Nonfunctional Requirements--}

Expand Down
8 changes: 4 additions & 4 deletions code/drasil-example/Drasil/NoPCM/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ import Drasil.SWHS.Changes (chgsStart, likeChg2, likeChg3, likeChg6)

import Data.Drasil.People (thulasi)
import Data.Drasil.Utils (enumSimple, refFromType,
itemRefToSent, makeTMatrix, itemRefToSent, weave, eqUnR)
itemRefToSent, makeTMatrix, itemRefToSent, weave, eqUnR, noRefs)
import Data.Drasil.Citations (parnasClements1986, smithLai2005)

import Data.Drasil.Concepts.Documentation as Doc (datumConstraint, inModel,
Expand Down Expand Up @@ -357,9 +357,9 @@ probDescIntro pro cp wa sw = foldlSP [getAcc pro, S "is a",
termAndDefn = termDefnF Nothing [termAndDefnBullets]

termAndDefnBullets :: Contents
termAndDefnBullets = Enumeration $ (Bullet $ map (\x -> Flat $
(at_start x) :+: S ":" +:+ (x ^. defn))
[ht_flux, heat_cap_spec, thermal_conduction, transient])
termAndDefnBullets = Enumeration $ Bullet $ noRefs $ map (\x -> Flat $
at_start x :+: S ":" +:+ (x ^. defn))
[ht_flux, heat_cap_spec, thermal_conduction, transient]

physSystDescription = physSystDesc (getAcc progName) fig_tank
[physSystDescList, fig_tank]
Expand Down
4 changes: 2 additions & 2 deletions code/drasil-example/Drasil/SSP/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ import Data.Drasil.Phrase (for)
import Data.Drasil.SentenceStructures (foldlList, foldlSP, foldlSent,
foldlSent_, ofThe, sAnd, sOr)
import Data.Drasil.SI_Units (degree, metre, newton, pascal)
import Data.Drasil.Utils (enumBullet, enumSimple, weave)
import Data.Drasil.Utils (enumBullet, enumSimple, weave, noRefsLT)
import Drasil.SSP.Assumptions (sspRefDB, sspAssumptions)
import Drasil.SSP.Changes (likelyChanges_SRS, unlikelyChanges_SRS)
import Drasil.SSP.DataDefs (ddRef, lengthLb, lengthLs, mobShrDerivation,
Expand Down Expand Up @@ -273,7 +273,7 @@ problem_desc = probDescF EmptyS ssa ending [termi_defi, phys_sys_desc, goal_stmt
-- SECTION 4.1.1 --
termi_defi = termDefnF Nothing [termi_defi_list]

termi_defi_list = Enumeration $ Simple $
termi_defi_list = Enumeration $ Simple $ noRefsLT $
map (\x -> (titleize $ x, Flat $ x ^. defn))
[fs_concept, crtSlpSrf, stress, strain, normForce,
shearForce, tension, compression, plnStrn]
Expand Down
12 changes: 6 additions & 6 deletions code/drasil-example/Drasil/SWHS/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -71,7 +71,7 @@ import Drasil.SWHS.Changes (likeChg1, likeChg2, likeChg3, likeChg4,
import Drasil.SWHS.DataDesc (swhsInputMod)

import Data.Drasil.Utils (enumSimple, weave, itemRefToSent, makeListRef,
makeTMatrix, refFromType, eqUnR)
makeTMatrix, refFromType, eqUnR, noRefs)
import Data.Drasil.SentenceStructures (acroIM, acroGD, acroGS, showingCxnBw,
foldlSent, foldlSent_, foldlSP, foldlSP_, foldlSPCol, foldlsC, isThe, ofThe,
ofThe', sAnd, sOf, foldlList)
Expand Down Expand Up @@ -242,7 +242,7 @@ systCont = SRS.sysCont [systCContents progName, sys_context_fig, systCIntro
progName user, systContRespBullets] []

systContRespBullets :: Contents
systContRespBullets = Enumeration $ Bullet $ [userResp input_ datum,
systContRespBullets = Enumeration $ Bullet $ noRefs [userResp input_ datum,
swhsResp]

--------------------------------
Expand Down Expand Up @@ -279,9 +279,9 @@ termAndDefn = termDefnF Nothing [termAndDefnBullets]
-- GlassBR has an additional sentence with a reference at the end.)

termAndDefnBullets :: Contents
termAndDefnBullets = Enumeration (Bullet $ map tAndDMap
termAndDefnBullets = Enumeration $ Bullet $ noRefs $ map tAndDMap
[CT.ht_flux, phase_change_material, CT.heat_cap_spec,
CT.thermal_conduction, transient])
CT.thermal_conduction, transient]

tAndDMap :: Concept c => c -> ItemType
tAndDMap c = Flat $ foldlSent [at_start c +: EmptyS, (c ^. defn)]
Expand Down Expand Up @@ -909,7 +909,7 @@ systCIntro pro us = foldlSPCol [short pro +:+. S "is mostly self-contained",
-- User Responsibilities --
userResp :: NamedChunk -> NamedChunk -> ItemType
userResp inp dat = Nested (titleize user +: S "Responsibilities")
$ Bullet $ map Flat [
$ Bullet $ noRefs $ map Flat [

foldlSent_ [S "Provide the", phrase inp, plural dat, S "to the",
phrase system `sC` S "ensuring no errors in the", plural dat, S "entry"],
Expand All @@ -922,7 +922,7 @@ userResp inp dat = Nested (titleize user +: S "Responsibilities")
-- SWHS Responsibilities --
swhsResp :: ItemType
swhsResp = Nested (short progName +: S "Responsibilities")
$ Bullet $ map Flat [
$ Bullet $ noRefs $ map Flat [

foldlSent_ [S "Detect", plural datum, S "type mismatch, such as a string of",
S "characters instead of a floating point number"],
Expand Down
4 changes: 2 additions & 2 deletions code/drasil-lang/Language/Drasil.hs
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,7 @@ module Language.Drasil (
, titleize, titleize', nounPhrase'', nounPhraseSP, nounPhraseSent
-- Document
, Referable(..), Document(..), DType(..), Section(..), Contents(..)
, SecCons(..), ListType(..), ItemType(..), ListPair
, SecCons(..), ListType(..), ItemType(..), ListTuple
, section, fig, figWithWidth, section''
, datadefn, reldefn
-- Reference
Expand Down Expand Up @@ -242,7 +242,7 @@ import Language.Drasil.Document (Document(..), DType(..)
, Section(..), Contents(..), SecCons(..), ListType(..), ItemType(..)
, section, fig, figWithWidth, section''
, datadefn, reldefn
, ListPair)
, ListTuple)
import Language.Drasil.Unicode -- all of it
import Language.Drasil.Development.UnitLang -- all of it
import Language.Drasil.Development.Unit -- all of it
Expand Down
12 changes: 6 additions & 6 deletions code/drasil-lang/Language/Drasil/Document.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,11 +21,11 @@ import Language.Drasil.UID

import Control.Lens ((^.), makeLenses)

data ListType = Bullet [ItemType] -- ^ Bulleted list
| Numeric [ItemType] -- ^ Enumerated List
| Simple [ListPair] -- ^ Simple list with items denoted by @-@
| Desc [ListPair] -- ^ Descriptive list, renders as "Title: Item" (see 'ListPair')
| Definitions [ListPair] -- ^ Renders a list of "@Title@ is the @Item@"
data ListType = Bullet [(ItemType,Maybe RefAdd)] -- ^ Bulleted list
| Numeric [(ItemType,Maybe RefAdd)] -- ^ Enumerated List
| Simple [ListTuple] -- ^ Simple list with items denoted by @-@
| Desc [ListTuple] -- ^ Descriptive list, renders as "Title: Item" (see 'ListTuple')
| Definitions [ListTuple] -- ^ Renders a list of "@Title@ is the @Item@"

data ItemType = Flat Sentence -- ^ Standard singular item
| Nested Header ListType -- ^ Nest a list as an item
Expand All @@ -42,7 +42,7 @@ type Header = Sentence -- Used when creating sublists
type Depth = Int
type Width = Float
type Height = Float
type ListPair = (Title,ItemType) -- ^ Title: Item
type ListTuple = (Title,ItemType,Maybe RefAdd) -- ^ Title: Item
type Filepath = String
type Lbl = Sentence

Expand Down
8 changes: 4 additions & 4 deletions code/drasil-lang/Language/Drasil/Document/Extract.hs
Original file line number Diff line number Diff line change
Expand Up @@ -139,8 +139,8 @@ getChg :: Change -> [Sentence]
getChg a = [chng a]

getLT :: ListType -> [Sentence]
getLT (Bullet it) = concatMap getIL it
getLT (Numeric it) = concatMap getIL it
getLT (Bullet it) = concatMap getIL $ map fst it
getLT (Numeric it) = concatMap getIL $ map fst it
getLT (Simple lp) = concatMap getLP lp
getLT (Desc lp) = concatMap getLP lp
getLT (Definitions lp) = concatMap getLP lp
Expand All @@ -150,8 +150,8 @@ getIL :: ItemType -> [Sentence]
getIL (Flat s) = [s]
getIL (Nested h lt) = h : getLT lt

getLP :: ListPair -> [Sentence]
getLP (t, it) = t : getIL it
getLP :: ListTuple -> [Sentence]
getLP (t, it, _) = t : getIL it

getBib :: (HasFields c) => [c] -> [Sentence]
getBib a = concatMap getField $ concatMap (^. getFields) a
Expand Down
14 changes: 9 additions & 5 deletions code/drasil-lang/Language/Drasil/Printing/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ import Language.Drasil.Spec (Sentence(..))
import Language.Drasil.Misc (unit'2Contents)
import Language.Drasil.NounPhrase (phrase, titleize)
import Language.Drasil.Reference (refAdd)
import Language.Drasil.RefTypes (RefAdd)
import Language.Drasil.Document (DType(DD, TM, Instance, General, Theory, Data),
ItemType(Nested, Flat), ListType(Definitions, Desc, Simple, Numeric, Bullet),
Contents(Bib, Graph, Defnt, Assumption, Change, Figure, Requirement, Enumeration,
Expand Down Expand Up @@ -328,17 +329,20 @@ layField sm (HowPublished (Verb v)) = P.HowPublished (P.Verb $ spec sm v)

-- | Translates lists
makeL :: HasSymbolTable ctx => ctx -> ListType -> P.ListType
makeL sm (Bullet bs) = P.Unordered $ map (\x -> (item sm x, Nothing)) bs
makeL sm (Numeric ns) = P.Ordered $ map (\x -> (item sm x, Nothing)) ns
makeL sm (Simple ps) = P.Simple $ map (\(x,y) -> (spec sm x, item sm y, Nothing)) ps
makeL sm (Desc ps) = P.Desc $ map (\(x,y) -> (spec sm x, item sm y, Nothing)) ps
makeL sm (Definitions ps) = P.Definitions $ map (\(x,y) -> (spec sm x, item sm y, Nothing)) ps
makeL sm (Bullet bs) = P.Unordered $ map (\(x,y) -> (item sm x, labref y)) bs
makeL sm (Numeric ns) = P.Ordered $ map (\(x,y) -> (item sm x, labref y)) ns
makeL sm (Simple ps) = P.Simple $ map (\(x,y,z) -> (spec sm x, item sm y, labref z)) ps
makeL sm (Desc ps) = P.Desc $ map (\(x,y,z) -> (spec sm x, item sm y, labref z)) ps
makeL sm (Definitions ps) = P.Definitions $ map (\(x,y,z) -> (spec sm x, item sm y, labref z)) ps

-- | Helper for translating list items
item :: HasSymbolTable ctx => ctx -> ItemType -> P.ItemType
item sm (Flat i) = P.Flat $ spec sm i
item sm (Nested t s) = P.Nested (spec sm t) (makeL sm s)

labref :: Maybe RefAdd -> Maybe P.Spec
labref l = maybe Nothing (\z -> Just $ P.S z) l

-- | Translates definitions
-- (Data defs, General defs, Theoretical models, etc.)
makePairs :: HasSymbolTable ctx => ctx -> DType -> [(String,[T.LayoutObj])]
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-lang/drasil-lang.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
Name: drasil-lang
Version: 0.1.4
Version: 0.1.5
Cabal-Version: >= 1.18
Author: Dan Szymczak, Steven Palmer, Jacques Carette, Spencer Smith
build-type: Simple
Expand Down

0 comments on commit 499239c

Please sign in to comment.