Skip to content

Commit

Permalink
Merge pull request #889 from JacquesCarette/minorGlassChanges
Browse files Browse the repository at this point in the history
Minor GlassBR Changes
  • Loading branch information
szymczdm authored Jul 17, 2018
2 parents d8e343f + a05f985 commit 46e5161
Show file tree
Hide file tree
Showing 22 changed files with 81 additions and 79 deletions.
7 changes: 5 additions & 2 deletions code/drasil-code/Language/Drasil/Code/Imperative/AST.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ module Language.Drasil.Code.Imperative.AST (
(#~),(#/^),(#|),(#+),(#-),(#*),(#/),(#%),(#^),
(&=),(&.=),(&=.),(&+=),(&-=),(&++),(&~-),(&.+=),(&.-=),(&.++),(&.~-),
($->),($.),($:),
log,exp,sin,cos,tan,csc,sec,cot,alwaysDel,neverDel,
log,ln,exp,sin,cos,tan,csc,sec,cot,alwaysDel,neverDel,
assign,at,binExpr,break,cast,cast',constDecDef,extends,for,forEach,ifCond,ifExists,listDec,listDecValues,listDec',
listOf,litBool,litChar,litFloat,litInt,litObj,litObj',litString,noElse,noParent,objDecDef,oneLiner,
param,params,paramToVar,
Expand Down Expand Up @@ -172,7 +172,7 @@ data Expression = UnaryExpr UnaryOp Value
| Exists Value --used to check whether the specified variable/list element/etc. is null
deriving (Eq, Show)
data UnaryOp = Negate | SquareRoot | Abs
| Not | Log | Exp
| Not | Log | Ln | Exp
| Sin | Cos | Tan
deriving (Eq, Show)
data BinaryOp = Equal | NotEqual | Greater | GreaterEqual | Less | LessEqual
Expand Down Expand Up @@ -447,6 +447,9 @@ n $: e = EnumElement n e
log :: Value -> Value
log = unExpr Log

ln :: Value -> Value
ln = unExpr Ln

exp :: Value -> Value
exp = unExpr Exp

Expand Down
3 changes: 2 additions & 1 deletion code/drasil-code/Language/Drasil/Code/Imperative/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ import Language.Drasil hiding (int, getLabel)
import Language.Drasil.Code.Code as C (CodeType(List, File, Char, Float, Object,
String, Boolean, Integer))
import Language.Drasil.Code.Imperative.AST as I hiding ((&=), State, assign, return,
Not, Tan, Cos, Sin, Exp, Abs, Log, And, Or)
Not, Tan, Cos, Sin, Exp, Abs, Log, Ln, And, Or)
import qualified Language.Drasil.Code.Imperative.AST as I (assign, return)
import Language.Drasil.Code.Imperative.LanguageRenderer (Options(..))
import Language.Drasil.Code.Imperative.Parsers.ConfigParser (pythonLabel, cppLabel, cSharpLabel, javaLabel)
Expand Down Expand Up @@ -497,6 +497,7 @@ renderRealInt s (UpFrom (Exc,a)) = sy s $> a
unop :: UFunc -> (Value -> Value)
unop Sqrt = (#/^)
unop Log = I.log
unop Ln = I.ln
unop Abs = (#|)
unop Exp = I.exp
unop Sin = I.sin
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -549,6 +549,7 @@ unOpDocD SquareRoot = text "sqrt"
unOpDocD Abs = text "fabs"
unOpDocD Not = text "!"
unOpDocD Log = text "log"
unOpDocD Ln = text "ln"
unOpDocD Exp = text "exp"
unOpDocD Sin = text "sin"
unOpDocD Cos = text "cos"
Expand All @@ -559,6 +560,7 @@ unOpDocD' SquareRoot = text "math.sqrt"
unOpDocD' Abs = text "math.fabs"
unOpDocD' Not = text "not"
unOpDocD' Log = text "math.log"
unOpDocD' Ln = text "math.ln"
unOpDocD' Exp = text "math.exp"
unOpDocD' Sin = text "math.sin"
unOpDocD' Cos = text "math.cos"
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-code/drasil-code.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ library
split >= 0.2.3.1,
MissingH >= 1.4.0.1,
parsec >= 3.1.9,
drasil-lang >= 0.1.3
drasil-lang >= 0.1.5
default-language: Haskell2010
ghc-options: -Wall -O2

Expand Down
4 changes: 2 additions & 2 deletions code/drasil-data/drasil-data.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -42,10 +42,10 @@ library
mtl >= 2.2.1,
directory >= 1.2.6.2,
split >= 0.2.3.1,
drasil-lang >= 0.1.3,
MissingH >= 1.4.0.1,
parsec >= 3.1.9,
data-fix (>= 0.0.4 && <= 1.0)
data-fix (>= 0.0.4 && <= 1.0),
drasil-lang >= 0.1.5
default-language: Haskell2010
ghc-options: -Wall

Expand Down
2 changes: 1 addition & 1 deletion code/drasil-docLang/Drasil/Sections/Stakeholders.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ stakehldrGeneral kWord clientDetails = (SRS.stakeholder) [stakeholderIntro] subs
-- general stakeholders introduction
stakeholderIntro :: Contents
stakeholderIntro = foldlSP [S "This", (phrase section_),
S "describes the" +: (titleize' stakeholder), S "the people who have an",
S "describes the" +: (plural stakeholder), S "the people who have an",
(phrase interest), S "in", (phrase $ the product_)]

tClientF :: (Idea a) => a -> Sentence -> Section
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-docLang/drasil-docLang.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ library
MissingH >= 1.4.0.1,
parsec >= 3.1.9,
data-fix (>= 0.0.4 && <= 1.0),
drasil-lang >= 0.1.1,
drasil-lang >= 0.1.5,
drasil-data >= 0.1.1
default-language: Haskell2010
ghc-options: -Wall
Expand Down
8 changes: 2 additions & 6 deletions code/drasil-example/Drasil/GlassBR/Body.hs
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@ mkSRS = RefSec (RefProg intro [TUnits, tsymb [TSPurpose, SymbOrder], TAandA]) :
capacity demandq probability)) :
SSDSec
(SSDProg
[SSDProblem (PDProg start gLassBR ending [terminology_and_description , physical_system_description, goal_statements])
[SSDProblem (PDProg start gLassBR ending [terminology_and_description, physical_system_description, goal_statements])
, SSDSolChSpec
(SCSProg
[ Assumptions
Expand All @@ -136,7 +136,7 @@ mkSRS = RefSec (RefProg intro [TUnits, tsymb [TSPurpose, SymbOrder], TAandA]) :
, IMs ([Label, Input, Output, InConstraints, OutConstraints] ++ stdFields) [probOfBreak, calofCapacity, calofDemand, testIMFromQD] HideDerivation
, Constraints EmptyS dataConstraintUncertainty
(foldlSent [(makeRef (SRS.valsOfAuxCons SRS.missingP [])), S "gives", (plural value `ofThe` S "specification"),
plural parameter, S "used in", (makeRef inputDataConstraints)] +:+ instance_models_intro2)
plural parameter, S "used in", (makeRef inputDataConstraints)])
[inputDataConstraints, outputDataConstraints]
]
)
Expand Down Expand Up @@ -478,10 +478,6 @@ assumptions = fst (foldr (\s (ls, n) -> ((Assumption $ assump ("A" ++ show n) s
inputDataConstraints = inDataConstTbl gbInputDataConstraints
outputDataConstraints = outDataConstTbl [prob_br]

instance_models_intro2 :: Sentence
instance_models_intro2 = foldlSent [makeRef outputDataConstraints, S "shows the",
plural constraint, S "that must be satisfied by the", phrase output_]

{--REQUIREMENTS--}

{--Functional Requirements--}
Expand Down
10 changes: 7 additions & 3 deletions code/drasil-example/Drasil/GlassBR/DataDefs.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,15 +78,15 @@ loadDFDD = mkDD loadDF [{-references-}] [{-derivation-}] ""--temporary

strDisFac_eq :: Expr
strDisFac_eq = apply (sy stressDistFac)
[sy dimlessLoad, (sy plate_len) / (sy plate_width)]
[sy dimlessLoad, sy aspectR]
--strDisFac_eq = FCall (asExpr interpZ) [V "SDF.txt", (sy plate_len) / (sy plate_width), sy dimlessLoad]

strDisFac :: QDefinition
strDisFac = mkDataDef stressDistFac strDisFac_eq

strDisFacDD :: DataDefinition
strDisFacDD = mkDD strDisFac [{-references-}] [{-derivation-}] ""--temporary
(Just $ [jRef2] ++ [qHtRef] ++ [aGrtrThanB])
(Just $ jRef2 : qHtRef : arRef : [])

--DD5--

Expand Down Expand Up @@ -145,7 +145,7 @@ tolPreDD = mkDD tolPre [{-references-}] [{-derivation-}] ""--temporary
--DD9--

tolStrDisFac_eq :: Expr
tolStrDisFac_eq = log (log (1 / (1 - (sy pb_tol)))
tolStrDisFac_eq = ln (ln (1 / (1 - (sy pb_tol)))
* ((((sy plate_len) * (sy plate_width)) $^ (sy sflawParamM - 1) /
((sy sflawParamK) * ((1000 * sy mod_elas *
(square (sy act_thick)))) $^ (sy sflawParamM) * (sy lDurFac)))))
Expand Down Expand Up @@ -188,6 +188,10 @@ aGrtrThanB = ((ch plate_len) `sC` (ch plate_width) +:+
S "are" +:+ plural dimension +:+ S "of the plate" `sC` S "where" +:+.
sParen (E (sy plate_len $> sy plate_width)))

arRef :: Sentence
arRef = (ch aspectR +:+ S "is the" +:+ phrase aspectR +:+.
S "defined in DD11")

hRef :: Sentence
hRef = (ch nom_thick +:+ S "is the true thickness" `sC`
S "which is based on the nominal thicknesses" +:+. S "as shown in DD2")
Expand Down
4 changes: 2 additions & 2 deletions code/drasil-example/Drasil/GlassBR/Unitals.hs
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,7 @@ char_weight = uqcND "char_weight" (nounPhraseSP "charge weight")

tNT = uvc "tNT" (nounPhraseSP "TNT equivalent factor")
(Atomic "TNT") Real
[ gtZeroConstr ] (1) defaultUncrt
[ gtZeroConstr ] (dbl 1.0) defaultUncrt

standOffDist = uqcND "standOffDist" (nounPhraseSP "stand off distance")
(Atomic "SD") metre Real
Expand Down Expand Up @@ -337,7 +337,7 @@ notSafe = dcc "notSafe" (nounPhraseSP "not safe")
probBreak = cc prob_br
("The fraction of glass lites or plies that would break at the first " ++
"occurrence of a specified load and duration, typically expressed " ++
"in lites per 1000.")
"in lites per 1000 [3]." {-astm2016-})
safeMessage = dcc "safeMessage" (nounPhraseSP "safe")
("For the given input parameters, the glass is considered safe.")
sD = cc' stdOffDist
Expand Down
14 changes: 7 additions & 7 deletions code/drasil-example/drasil-example.cabal
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
Name: drasil-example
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 All @@ -19,7 +19,7 @@ executable tiny
mtl >= 2.2.1,
directory >= 1.2.6.2,
split >= 0.2.3.1,
drasil-lang >= 0.1.3,
drasil-lang >= 0.1.5,
drasil-data >= 0.1.1,
drasil-code >= 0.1.1,
drasil-gen >= 0.1.0,
Expand Down Expand Up @@ -57,7 +57,7 @@ executable nopcm
mtl >= 2.2.1,
directory >= 1.2.6.2,
split >= 0.2.3.1,
drasil-lang >= 0.1.3,
drasil-lang >= 0.1.5,
drasil-data >= 0.1.1,
drasil-code >= 0.1.1,
drasil-gen >= 0.1.0,
Expand Down Expand Up @@ -91,7 +91,7 @@ executable ssp
mtl >= 2.2.1,
directory >= 1.2.6.2,
split >= 0.2.3.1,
drasil-lang >= 0.1.3,
drasil-lang >= 0.1.5,
drasil-data >= 0.1.1,
drasil-code >= 0.1.1,
drasil-gen >= 0.1.0,
Expand Down Expand Up @@ -123,7 +123,7 @@ executable glassbr
mtl >= 2.2.1,
directory >= 1.2.6.2,
split >= 0.2.3.1,
drasil-lang >= 0.1.3,
drasil-lang >= 0.1.5,
drasil-data >= 0.1.1,
drasil-code >= 0.1.1,
drasil-gen >= 0.1.0,
Expand Down Expand Up @@ -151,7 +151,7 @@ executable chipmunkdocs
mtl >= 2.2.1,
directory >= 1.2.6.2,
split >= 0.2.3.1,
drasil-lang >= 0.1.3,
drasil-lang >= 0.1.5,
drasil-data >= 0.1.1,
drasil-code >= 0.1.1,
drasil-gen >= 0.1.0,
Expand Down Expand Up @@ -183,7 +183,7 @@ executable swhs
pretty >= 1.1.1.1,
mtl >= 2.2.1,
directory >= 1.2.6.2,
drasil-lang >= 0.1.3,
drasil-lang >= 0.1.5,
drasil-data >= 0.1.1,
drasil-code >= 0.1.1,
drasil-gen >= 0.1.0,
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-gen/drasil-gen.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ library
split >= 0.2.3.1,
MissingH >= 1.4.0.1,
parsec >= 3.1.9,
drasil-lang >= 0.1.3,
drasil-lang >= 0.1.5,
drasil-code >= 0.1.3
default-language: Haskell2010
ghc-options: -Wall -O2
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 @@ -17,7 +17,7 @@ module Language.Drasil (
, Relation, RealInterval(..), Inclusive(..)
, ($=), ($<), ($<=), ($>), ($>=), ($^), ($&&), ($||), ($=>), ($<=>), ($.)
-- Expr.Math
, log, abs, sin, cos, tan, sec, csc, cot, exp, sqrt, square, euclidean, vars
, log, ln, abs, sin, cos, tan, sec, csc, cot, exp, sqrt, square, euclidean, vars
, dim, idx, int, dbl, str, isin, case_
, sum_all, defsum, prod_all, defprod, defint, int_all
, real_interval
Expand Down Expand Up @@ -226,7 +226,7 @@ import Language.Drasil.SystemInformation
import Language.Drasil.Expr (Expr(..), BinOp(..), UFunc(..), ArithOper(..),
BoolOper(..), Relation, RealInterval(..), Inclusive(..),
($=), ($<), ($<=), ($>), ($>=), ($^), ($&&), ($||), ($=>), ($<=>), ($.))
import Language.Drasil.Expr.Math (log, sin, cos, tan, sqrt, square, sec, csc, cot, exp,
import Language.Drasil.Expr.Math (log, ln, sin, cos, tan, sqrt, square, sec, csc, cot, exp,
dim, idx, int, dbl, str, isin, case_,
sum_all, defsum, prod_all, defprod,
real_interval,
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-lang/Language/Drasil/Expr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ data ArithOper = Add | Mul deriving (Eq)
data BoolOper = And | Or deriving (Eq)

-- | Unary functions
data UFunc = Norm | Abs | Log | Sin | Cos | Tan | Sec | Csc | Cot | Exp
data UFunc = Norm | Abs | Log | Ln | Sin | Cos | Tan | Sec | Csc | Cot | Exp
| Sqrt | Not | Neg | Dim

-- | Drasil Expressions
Expand Down
4 changes: 4 additions & 0 deletions code/drasil-lang/Language/Drasil/Expr/Math.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,10 @@ import Language.Drasil.Classes (HasUID(uid), HasSymbol)
log :: Expr -> Expr
log = UnaryOp Log

-- | Smart constructor to take the ln of an expression
ln :: Expr -> Expr
ln = UnaryOp Ln

-- | Smart constructor to take the square root of an expression
sqrt :: Expr -> Expr
sqrt = UnaryOp Sqrt
Expand Down
3 changes: 2 additions & 1 deletion code/drasil-lang/Language/Drasil/HTML/Print.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Language.Drasil.Printing.Import (makeDocument)
import Language.Drasil.Printing.AST (Spec, ItemType(Flat, Nested),
ListType(Ordered, Unordered, Definitions, Desc, Simple), Expr, Fence(Curly, Paren, Abs, Norm),
Ops(Prod, Inte, Mul, Summ, Or, Add, And, Subt, Iff, Impl, GEq, LEq, Lt, Gt, NEq, Eq,
Dot, Cross, Neg, Exp, Not, Dim, Cot, Csc, Sec, Tan, Cos, Sin, Log, Prime, Comma, Boolean,
Dot, Cross, Neg, Exp, Not, Dim, Cot, Csc, Sec, Tan, Cos, Sin, Log, Ln, Prime, Comma, Boolean,
Real, Rational, Natural, Integer, IsIn),
Expr(Sub, Sup, Over, Sqrt, Spc, Font, MO, Fenced, Spec, Ident, Row, Mtx, Case, Div, Str,
Int, Dbl), Spec(Quote, EmptyS, Ref, HARDNL, Sp, Sy, S, E, (:+:)),
Expand Down Expand Up @@ -174,6 +174,7 @@ p_ops Boolean = "&#120121;"
p_ops Comma = ","
p_ops Prime = "&prime;"
p_ops Log = "log"
p_ops Ln = "ln"
p_ops Sin = "sin"
p_ops Cos = "cos"
p_ops Tan = "tan"
Expand Down
4 changes: 2 additions & 2 deletions code/drasil-lang/Language/Drasil/Printing/AST.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,8 +5,8 @@ import Language.Drasil.RefTypes (RefType, RefAdd)
import Language.Drasil.Unicode (Special)
import Language.Drasil.Chunk.ShortName (ShortName)

data Ops = IsIn | Integer | Real | Rational | Natural | Boolean | Comma | Prime | Log
| Sin | Cos | Tan | Sec | Csc | Cot | Not | Dim | Exp | Neg | Cross
data Ops = IsIn | Integer | Real | Rational | Natural | Boolean | Comma | Prime | Log
| Ln | Sin | Cos | Tan | Sec | Csc | Cot | Not | Dim | Exp | Neg | Cross
| Dot | Eq | NEq | Lt | Gt | LEq | GEq | Impl | Iff | Subt | And | Or
| Add | Mul | Summ | Inte | Prod

Expand Down
1 change: 1 addition & 0 deletions code/drasil-lang/Language/Drasil/Printing/Import.hs
Original file line number Diff line number Diff line change
Expand Up @@ -97,6 +97,7 @@ expr (Case ps) sm = if length ps < 2 then
else P.Case (zip (map (flip expr sm . fst) ps) (map (flip expr sm . snd) ps))
expr (Matrix a) sm = P.Mtx $ map (map (flip expr sm)) a
expr (UnaryOp Log u) sm = mkCall sm P.Log u
expr (UnaryOp Ln u) sm = mkCall sm P.Ln u
expr (UnaryOp Sin u) sm = mkCall sm P.Sin u
expr (UnaryOp Cos u) sm = mkCall sm P.Cos u
expr (UnaryOp Tan u) sm = mkCall sm P.Tan u
Expand Down
37 changes: 19 additions & 18 deletions code/drasil-lang/Language/Drasil/TeX/Print.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import Language.Drasil.Printing.AST (Spec, ItemType(Nested, Flat),
Fence(Norm, Abs, Curly, Paren), Expr,
Ops(Inte, Prod, Summ, Mul, Add, Or, And, Subt, Iff, LEq, GEq,
NEq, Eq, Gt, Lt, Impl, Dot, Cross, Neg, Exp, Dim, Not, Cot,
Csc, Sec, Tan, Cos, Sin, Log, Prime, Comma, Boolean, Real, Natural,
Csc, Sec, Tan, Cos, Sin, Log, Ln, Prime, Comma, Boolean, Real, Natural,
Rational, Integer, IsIn), Spacing(Thin), Fonts(Emph, Bold),
Expr(Spc, Sqrt, Font, Fenced, MO, Over, Sup, Sub, Ident, Spec, Row,
Mtx, Div, Case, Str, Int, Dbl), OverSymb(Hat), Label)
Expand Down Expand Up @@ -130,7 +130,7 @@ p_expr (Spc Thin) = "\\,"
p_expr (Sqrt e) = "\\sqrt{" ++ p_expr e ++ "}"

p_ops :: Ops -> String
p_ops IsIn = "\\in{}"
p_ops IsIn = "\\in{}"
p_ops Integer = "\\mathbb{Z}"
p_ops Rational = "\\mathbb{Q}"
p_ops Real = "\\mathbb{R}"
Expand All @@ -139,6 +139,7 @@ p_ops Boolean = "\\mathbb{B}"
p_ops Comma = ","
p_ops Prime = "'"
p_ops Log = "\\log"
p_ops Ln = "\\ln"
p_ops Sin = "\\sin"
p_ops Cos = "\\cos"
p_ops Tan = "\\tan"
Expand All @@ -151,22 +152,22 @@ p_ops Exp = "e"
p_ops Neg = "-"
p_ops Cross = "\\times"
p_ops Dot = "\\cdot{}"
p_ops Eq = "="
p_ops NEq = "\\neq{}"
p_ops Lt = "<"
p_ops Gt = ">"
p_ops GEq = "\\geq{}"
p_ops LEq = "\\leq{}"
p_ops Impl = "\\implies{}"
p_ops Iff = "\\iff{}"
p_ops Subt = "-"
p_ops And = "\\land{}"
p_ops Or = "\\lor{}"
p_ops Add = "+"
p_ops Mul = " "
p_ops Summ = "\\displaystyle\\sum"
p_ops Prod = "\\displaystyle\\prod"
p_ops Inte = "\\int"
p_ops Eq = "="
p_ops NEq = "\\neq{}"
p_ops Lt = "<"
p_ops Gt = ">"
p_ops GEq = "\\geq{}"
p_ops LEq = "\\leq{}"
p_ops Impl = "\\implies{}"
p_ops Iff = "\\iff{}"
p_ops Subt = "-"
p_ops And = "\\land{}"
p_ops Or = "\\lor{}"
p_ops Add = "+"
p_ops Mul = " "
p_ops Summ = "\\displaystyle\\sum"
p_ops Prod = "\\displaystyle\\prod"
p_ops Inte = "\\int"

fence :: OpenClose -> Fence -> String
fence Open Paren = "\\left("
Expand Down
Loading

0 comments on commit 46e5161

Please sign in to comment.