{-# Language TemplateHaskell, RankNTypes #-}
module Theory.Drasil.Theory (
Theory(..),
TheoryModel,
tm, tmNoRefs) where
import Control.Lens (Lens', view, makeLenses)
import Language.Drasil
import Language.Drasil.Development (showUID)
import Data.Drasil.TheoryConcepts (thModel)
import Theory.Drasil.ModelKinds
class Theory t where
valid_context :: Lens' t [TheoryModel]
spaces :: Lens' t [SpaceDefn]
quantities :: Lens' t [QuantityDict]
operations :: Lens' t [ConceptChunk]
defined_quant :: Lens' t [ModelQDef]
invariants :: Lens' t [ModelExpr]
defined_fun :: Lens' t [ModelQDef]
data SpaceDefn
data TheoryModel = TM
{ TheoryModel -> ModelKind ModelExpr
_mk :: ModelKind ModelExpr
, TheoryModel -> [TheoryModel]
_vctx :: [TheoryModel]
, TheoryModel -> [SpaceDefn]
_spc :: [SpaceDefn]
, TheoryModel -> [QuantityDict]
_quan :: [QuantityDict]
, TheoryModel -> [ConceptChunk]
_ops :: [ConceptChunk]
, TheoryModel -> [ModelQDef]
_defq :: [ModelQDef]
, TheoryModel -> [ModelExpr]
_invs :: [ModelExpr]
, TheoryModel -> [ModelQDef]
_dfun :: [ModelQDef]
, TheoryModel -> [DecRef]
_rf :: [DecRef]
, TheoryModel -> ShortName
lb :: ShortName
, TheoryModel -> String
ra :: String
, TheoryModel -> [Sentence]
_notes :: [Sentence]
}
makeLenses ''TheoryModel
instance HasUID TheoryModel where uid :: Lens' TheoryModel UID
uid = Lens' TheoryModel (ModelKind ModelExpr)
mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. HasUID c => Lens' c UID
uid
instance NamedIdea TheoryModel where term :: Lens' TheoryModel NP
term = Lens' TheoryModel (ModelKind ModelExpr)
mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. NamedIdea c => Lens' c NP
term
instance Idea TheoryModel where getA :: TheoryModel -> Maybe String
getA = forall c. Idea c => c -> Maybe String
getA forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Lens' TheoryModel (ModelKind ModelExpr)
mk
instance Definition TheoryModel where defn :: Lens' TheoryModel Sentence
defn = Lens' TheoryModel (ModelKind ModelExpr)
mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall c. Definition c => Lens' c Sentence
defn
instance HasDecRef TheoryModel where getDecRefs :: Lens' TheoryModel [DecRef]
getDecRefs = Lens' TheoryModel [DecRef]
rf
instance ConceptDomain TheoryModel where cdom :: TheoryModel -> [UID]
cdom = forall c. ConceptDomain c => c -> [UID]
cdom forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Lens' TheoryModel (ModelKind ModelExpr)
mk
instance HasAdditionalNotes TheoryModel where getNotes :: Lens' TheoryModel [Sentence]
getNotes = Lens' TheoryModel [Sentence]
notes
instance Theory TheoryModel where
valid_context :: Lens' TheoryModel [TheoryModel]
valid_context = Lens' TheoryModel [TheoryModel]
vctx
spaces :: Lens' TheoryModel [SpaceDefn]
spaces = Lens' TheoryModel [SpaceDefn]
spc
quantities :: Lens' TheoryModel [QuantityDict]
quantities = Lens' TheoryModel [QuantityDict]
quan
operations :: Lens' TheoryModel [ConceptChunk]
operations = Lens' TheoryModel [ConceptChunk]
ops
defined_quant :: Lens' TheoryModel [ModelQDef]
defined_quant = Lens' TheoryModel [ModelQDef]
defq
invariants :: Lens' TheoryModel [ModelExpr]
invariants = Lens' TheoryModel [ModelExpr]
invs
defined_fun :: Lens' TheoryModel [ModelQDef]
defined_fun = Lens' TheoryModel [ModelQDef]
dfun
instance HasShortName TheoryModel where shortname :: TheoryModel -> ShortName
shortname = TheoryModel -> ShortName
lb
instance HasRefAddress TheoryModel where getRefAdd :: TheoryModel -> LblType
getRefAdd TheoryModel
l = IRefProg -> String -> LblType
RP (String -> IRefProg
prepend forall a b. (a -> b) -> a -> b
$ forall c. CommonIdea c => c -> String
abrv TheoryModel
l) (TheoryModel -> String
ra TheoryModel
l)
instance CommonIdea TheoryModel where abrv :: TheoryModel -> String
abrv TheoryModel
_ = forall c. CommonIdea c => c -> String
abrv CI
thModel
instance Referable TheoryModel where
refAdd :: TheoryModel -> String
refAdd = TheoryModel -> String
ra
renderRef :: TheoryModel -> LblType
renderRef TheoryModel
l = IRefProg -> String -> LblType
RP (String -> IRefProg
prepend forall a b. (a -> b) -> a -> b
$ forall c. CommonIdea c => c -> String
abrv TheoryModel
l) (forall s. Referable s => s -> String
refAdd TheoryModel
l)
tm :: (Quantity q, MayHaveUnit q, Concept c) => ModelKind ModelExpr ->
[q] -> [c] -> [ModelQDef] ->
[ModelExpr] -> [ModelQDef] -> [DecRef] ->
String -> [Sentence] -> TheoryModel
tm :: forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> String
-> [Sentence]
-> TheoryModel
tm ModelKind ModelExpr
mkind [q]
_ [c]
_ [ModelQDef]
_ [ModelExpr]
_ [ModelQDef]
_ [] String
_ = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Source field of " forall a. [a] -> [a] -> [a]
++ forall a. HasUID a => a -> String
showUID ModelKind ModelExpr
mkind forall a. [a] -> [a] -> [a]
++ String
" is empty"
tm ModelKind ModelExpr
mkind [q]
q [c]
c [ModelQDef]
dq [ModelExpr]
inv [ModelQDef]
dfn [DecRef]
r String
lbe =
ModelKind ModelExpr
-> [TheoryModel]
-> [SpaceDefn]
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> ShortName
-> String
-> [Sentence]
-> TheoryModel
TM ModelKind ModelExpr
mkind [] [] (forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [q]
q) (forall a b. (a -> b) -> [a] -> [b]
map forall c. Concept c => c -> ConceptChunk
cw [c]
c) [ModelQDef]
dq [ModelExpr]
inv [ModelQDef]
dfn [DecRef]
r (Sentence -> ShortName
shortname' forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
lbe)
(forall c. CommonIdea c => c -> String -> String
prependAbrv CI
thModel String
lbe)
tmNoRefs :: (Quantity q, MayHaveUnit q, Concept c) => ModelKind ModelExpr ->
[q] -> [c] -> [ModelQDef] -> [ModelExpr] -> [ModelQDef] ->
String -> [Sentence] -> TheoryModel
tmNoRefs :: forall q c.
(Quantity q, MayHaveUnit q, Concept c) =>
ModelKind ModelExpr
-> [q]
-> [c]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> String
-> [Sentence]
-> TheoryModel
tmNoRefs ModelKind ModelExpr
mkind [q]
q [c]
c [ModelQDef]
dq [ModelExpr]
inv [ModelQDef]
dfn String
lbe =
ModelKind ModelExpr
-> [TheoryModel]
-> [SpaceDefn]
-> [QuantityDict]
-> [ConceptChunk]
-> [ModelQDef]
-> [ModelExpr]
-> [ModelQDef]
-> [DecRef]
-> ShortName
-> String
-> [Sentence]
-> TheoryModel
TM ModelKind ModelExpr
mkind [] [] (forall a b. (a -> b) -> [a] -> [b]
map forall q. (Quantity q, MayHaveUnit q) => q -> QuantityDict
qw [q]
q) (forall a b. (a -> b) -> [a] -> [b]
map forall c. Concept c => c -> ConceptChunk
cw [c]
c) [ModelQDef]
dq [ModelExpr]
inv [ModelQDef]
dfn [] (Sentence -> ShortName
shortname' forall a b. (a -> b) -> a -> b
$ String -> Sentence
S String
lbe)
(forall c. CommonIdea c => c -> String -> String
prependAbrv CI
thModel String
lbe)