{-# LANGUAGE PostfixOperators #-} module Drasil.Projectile.Assumptions (accelYGravity, accelXZero, cartSyst, assumptions, constAccel, gravAccelValue, launchOrigin, pointMass, posXDirection, targetXAxis, timeStartZero, twoDMotion, yAxisGravity) where import Language.Drasil import Language.Drasil.Chunk.Concept.NamedCombinators import qualified Language.Drasil.NounPhrase.Combinators as NP import qualified Language.Drasil.Sentence.Combinators as S import qualified Drasil.DocLang.SRS as SRS (valsOfAuxCons) import Data.Drasil.Concepts.Documentation (assumpDom, value, consVals) import Data.Drasil.Concepts.Math (cartesian, xAxis, xDir, yAxis, yDir, direction, positive) import Data.Drasil.Concepts.PhysicalProperties (mass) import Data.Drasil.Concepts.Physics (acceleration, collision, distance, gravity, time, twoD) import Drasil.Projectile.Concepts (launcher, projectile, target, projMotion) assumptions :: [ConceptInstance] assumptions :: [ConceptInstance] assumptions = [ConceptInstance twoDMotion, ConceptInstance cartSyst, ConceptInstance yAxisGravity, ConceptInstance launchOrigin, ConceptInstance targetXAxis, ConceptInstance posXDirection, ConceptInstance constAccel, ConceptInstance accelXZero, ConceptInstance accelYGravity, ConceptInstance neglectDrag, ConceptInstance pointMass, ConceptInstance freeFlight, ConceptInstance neglectCurv, ConceptInstance timeStartZero, ConceptInstance gravAccelValue] twoDMotion, cartSyst, yAxisGravity, launchOrigin, targetXAxis, posXDirection, constAccel, accelXZero, accelYGravity, neglectDrag, pointMass, freeFlight, neglectCurv, timeStartZero, gravAccelValue :: ConceptInstance twoDMotion :: ConceptInstance twoDMotion = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "twoDMotion" Sentence twoDMotionDesc String "twoDMotion" ConceptChunk assumpDom cartSyst :: ConceptInstance cartSyst = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "cartSyst" Sentence cartSystDesc String "cartSyst" ConceptChunk assumpDom yAxisGravity :: ConceptInstance yAxisGravity = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "yAxisGravity" Sentence yAxisGravityDesc String "yAxisGravity" ConceptChunk assumpDom launchOrigin :: ConceptInstance launchOrigin = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "launchOrigin" Sentence launchOriginDesc String "launchOrigin" ConceptChunk assumpDom targetXAxis :: ConceptInstance targetXAxis = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "targetXAxis" Sentence targetXAxisDesc String "targetXAxis" ConceptChunk assumpDom posXDirection :: ConceptInstance posXDirection = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "posXDirection" Sentence posXDirectionDesc String "posXDirection" ConceptChunk assumpDom constAccel :: ConceptInstance constAccel = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "constAccel" Sentence constAccelDesc String "constAccel" ConceptChunk assumpDom accelXZero :: ConceptInstance accelXZero = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "accelXZero" Sentence accelXZeroDesc String "accelXZero" ConceptChunk assumpDom accelYGravity :: ConceptInstance accelYGravity = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "accelYGravity" Sentence accelYGravityDesc String "accelYGravity" ConceptChunk assumpDom neglectDrag :: ConceptInstance neglectDrag = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "neglectDrag" Sentence neglectDragDesc String "neglectDrag" ConceptChunk assumpDom pointMass :: ConceptInstance pointMass = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "pointMass" Sentence pointMassDesc String "pointMass" ConceptChunk assumpDom freeFlight :: ConceptInstance freeFlight = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "freeFlight" Sentence freeFlightDesc String "freeFlight" ConceptChunk assumpDom neglectCurv :: ConceptInstance neglectCurv = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "neglectCurv" Sentence neglectCurvDesc String "neglectCurv" ConceptChunk assumpDom timeStartZero :: ConceptInstance timeStartZero = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "timeStartZero" Sentence timeStartZeroDesc String "timeStartZero" ConceptChunk assumpDom gravAccelValue :: ConceptInstance gravAccelValue = forall c. Concept c => String -> Sentence -> String -> c -> ConceptInstance cic String "gravAccelValue" Sentence gravAccelValueDesc String "gravAccelValue" ConceptChunk assumpDom twoDMotionDesc :: Sentence twoDMotionDesc :: Sentence twoDMotionDesc = forall n. NounPhrase n => n -> Sentence atStartNP (NP -> NP NP.the (IdeaDict projMotion forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP `is` CI twoD)) Sentence -> Sentence -> Sentence +:+. Sentence -> Sentence sParen (CI -> Sentence getAcc CI twoD) cartSystDesc :: Sentence cartSystDesc :: Sentence cartSystDesc = forall n. NounPhrase n => n -> Sentence atStartNP (forall c. NamedIdea c => c -> NP a_ ConceptChunk cartesian) Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "used" Sentence -> Sentence -> Sentence +:+. forall r. (Referable r, HasShortName r) => r -> Sentence fromSource ConceptInstance neglectCurv yAxisGravityDesc :: Sentence yAxisGravityDesc :: Sentence yAxisGravityDesc = forall n. NounPhrase n => n -> Sentence atStartNP (ConceptChunk direction forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP `the_ofThe` ConceptChunk yAxis) Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "directed opposite to" Sentence -> Sentence -> Sentence +:+. forall n. NamedIdea n => n -> Sentence phrase ConceptChunk gravity launchOriginDesc :: Sentence launchOriginDesc :: Sentence launchOriginDesc = (forall n. NounPhrase n => n -> Sentence atStartNP (forall c. NamedIdea c => c -> NP the ConceptChunk launcher) Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "coincident with the origin" !.) targetXAxisDesc :: Sentence targetXAxisDesc :: Sentence targetXAxisDesc = forall n. NounPhrase n => n -> Sentence atStartNP (forall c. NamedIdea c => c -> NP the ConceptChunk target) Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "lies on the" Sentence -> Sentence -> Sentence +:+ forall n. NamedIdea n => n -> Sentence phrase ConceptChunk xAxis Sentence -> Sentence -> Sentence +:+. forall r. (Referable r, HasShortName r) => r -> Sentence fromSource ConceptInstance neglectCurv posXDirectionDesc :: Sentence posXDirectionDesc :: Sentence posXDirectionDesc = forall n. NounPhrase n => n -> Sentence atStartNP (NP -> NP NP.the (forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP combineNINI ConceptChunk positive ConceptChunk xDir)) Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "from the" Sentence -> Sentence -> Sentence +:+. forall n. NounPhrase n => n -> Sentence phraseNP (ConceptChunk launcher forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP `toThe` ConceptChunk target) constAccelDesc :: Sentence constAccelDesc :: Sentence constAccelDesc = forall n. NounPhrase n => n -> Sentence atStartNP (forall c. NamedIdea c => c -> NP the ConceptChunk acceleration) Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "constant" Sentence -> Sentence -> Sentence +:+. forall r. (Referable r, HasShortName r) => [r] -> Sentence fromSources [ConceptInstance accelXZero, ConceptInstance accelYGravity, ConceptInstance neglectDrag, ConceptInstance freeFlight] accelXZeroDesc :: Sentence accelXZeroDesc :: Sentence accelXZeroDesc = forall n. NounPhrase n => n -> Sentence atStartNP (NP -> NP NP.the (ConceptChunk acceleration forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP `inThe` ConceptChunk xDir)) Sentence -> Sentence -> Sentence `S.is` (String -> Sentence S String "zero" !.) accelYGravityDesc :: Sentence accelYGravityDesc :: Sentence accelYGravityDesc = forall n. NounPhrase n => n -> Sentence atStartNP (NP -> NP NP.the (ConceptChunk acceleration forall c d. (NamedIdea c, NamedIdea d) => c -> d -> NP `inThe` ConceptChunk yDir)) Sentence -> Sentence -> Sentence `S.isThe` forall n. NamedIdea n => n -> Sentence phrase ConceptChunk acceleration Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "due to" Sentence -> Sentence -> Sentence +:+ forall n. NamedIdea n => n -> Sentence phrase ConceptChunk gravity Sentence -> Sentence -> Sentence +:+. forall r. (Referable r, HasShortName r) => r -> Sentence fromSource ConceptInstance yAxisGravity neglectDragDesc :: Sentence neglectDragDesc :: Sentence neglectDragDesc = (String -> Sentence S String "Air drag" Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "neglected" !.) pointMassDesc :: Sentence pointMassDesc :: Sentence pointMassDesc = (String -> Sentence S String "size" Sentence -> Sentence -> Sentence `S.and_` String -> Sentence S String "shape") Sentence -> Sentence -> Sentence `S.the_ofTheC` forall n. NamedIdea n => n -> Sentence phrase ConceptChunk projectile Sentence -> Sentence -> Sentence `S.are` String -> Sentence S String "negligible" Sentence -> Sentence -> Sentence `sC` String -> Sentence S String "so that it can be modelled as a point" Sentence -> Sentence -> Sentence +:+. forall n. NamedIdea n => n -> Sentence phrase ConceptChunk mass freeFlightDesc :: Sentence freeFlightDesc :: Sentence freeFlightDesc = String -> Sentence S String "The flight" Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "free; there" Sentence -> Sentence -> Sentence `S.are` String -> Sentence S String "no" Sentence -> Sentence -> Sentence +:+ forall n. NamedIdea n => n -> Sentence plural ConceptChunk collision Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "during" Sentence -> Sentence -> Sentence +:+. (String -> Sentence S String "trajectory" Sentence -> Sentence -> Sentence `S.the_ofThe` forall n. NamedIdea n => n -> Sentence phrase ConceptChunk projectile) neglectCurvDesc :: Sentence neglectCurvDesc :: Sentence neglectCurvDesc = forall n. NounPhrase n => n -> Sentence atStartNP (forall c. NamedIdea c => c -> NP the ConceptChunk distance) Sentence -> Sentence -> Sentence `S.is` String -> Sentence S String "small enough that" Sentence -> Sentence -> Sentence +:+. (String -> Sentence S String "curvature" Sentence -> Sentence -> Sentence `S.the_ofThe` String -> Sentence S String "celestial body can be neglected") timeStartZeroDesc :: Sentence timeStartZeroDesc :: Sentence timeStartZeroDesc = forall n. NamedIdea n => n -> Sentence atStart ConceptChunk time Sentence -> Sentence -> Sentence +:+. String -> Sentence S String "starts at zero" gravAccelValueDesc :: Sentence gravAccelValueDesc :: Sentence gravAccelValueDesc = forall n. NounPhrase n => n -> Sentence atStartNP (forall c. NamedIdea c => c -> NP the ConceptChunk acceleration) Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "due to" Sentence -> Sentence -> Sentence +:+ forall n. NamedIdea n => n -> Sentence phrase ConceptChunk gravity Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "is assumed to have the" Sentence -> Sentence -> Sentence +:+ forall n. NamedIdea n => n -> Sentence phrase IdeaDict value Sentence -> Sentence -> Sentence +:+ String -> Sentence S String "provided in the section for" Sentence -> Sentence -> Sentence +:+. forall r. (HasUID r, HasRefAddress r, HasShortName r) => r -> Sentence -> Sentence namedRef ([Contents] -> [Section] -> Section SRS.valsOfAuxCons [] []) (forall n. NamedIdea n => n -> Sentence titleize IdeaDict consVals)