Skip to content

Commit

Permalink
Renamed Jupyter Notebook Doctype and Format (#3832)
Browse files Browse the repository at this point in the history
* renamed Jupter Notebook related formats and doctypes

* renamed generage projectile lesson
  • Loading branch information
BilalM04 committed Jul 7, 2024
1 parent 72ae024 commit a33094f
Show file tree
Hide file tree
Showing 28 changed files with 49 additions and 49 deletions.
2 changes: 1 addition & 1 deletion code/drasil-example/dblpend/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,6 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "DblPend_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "DblPend_SRS") srs printSetting
genCode choices code
genDot fullSI
2 changes: 1 addition & 1 deletion code/drasil-example/gamephysics/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "GamePhysics_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "GamePhysics_SRS") srs printSetting
genDot fullSI
-- When ready to generate code from GamePhysics, uncomment the next line and all of Choices.hs
-- genCode choices code
2 changes: 1 addition & 1 deletion code/drasil-example/glassbr/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,6 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "GlassBR_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "GlassBR_SRS") srs printSetting
genCode choices code
genDot fullSI
2 changes: 1 addition & 1 deletion code/drasil-example/hghc/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "HGHC_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "HGHC_SRS") srs printSetting
-- When ready to generate code, uncomment this file and Choices.hs
--genCode thisChoices thisCode
-- When ready to generate traceability graphs, uncomment this and import genDot and fullSI:
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-example/pdcontroller/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,6 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "PDController_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "PDController_SRS") srs printSetting
genCode codeChoices codeSpecs
genDot fullSI
6 changes: 3 additions & 3 deletions code/drasil-example/projectile/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@ module Main (main) where

import GHC.IO.Encoding
import Language.Drasil.Generate (gen, typeCheckSI, genDot,
DocSpec(DocSpec), DocType(SRS,Jupyter), Format(..), docChoices,
DocSpec(DocSpec), DocType(SRS, Lesson), Format(..), docChoices,
dumpEverything)
import Drasil.Projectile.Body (printSetting, srs, fullSI)
import Drasil.Projectile.Choices (choiceCombos, genCodeWithChoices)
Expand All @@ -16,8 +16,8 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "Projectile_SRS") srs printSetting
gen (DocSpec (docChoices Jupyter []) "Projectile Lesson") PL.nb PL.printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "Projectile_SRS") srs printSetting
gen (DocSpec (docChoices Lesson []) "Projectile_Lesson") PL.nb PL.printSetting
genCodeWithChoices choiceCombos
genDot fullSI
-- if the chunkDB had a mutable state, then this would make more sense.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,11 @@ module Drasil.Projectile.Lesson.Main (main) where

import GHC.IO.Encoding

import Language.Drasil.Generate (gen, DocSpec(DocSpec), DocType(Jupyter), docChoices)
import Language.Drasil.Generate (gen, DocSpec(DocSpec), DocType(Lesson), docChoices)

import Drasil.Projectile.Lesson.Body (nb, printSetting)

main :: IO()
main = do
setLocaleEncoding utf8
gen (DocSpec (docChoices Jupyter []) "Projectile Lesson") nb printSetting
gen (DocSpec (docChoices Lesson []) "Projectile_Lesson") nb printSetting
2 changes: 1 addition & 1 deletion code/drasil-example/sglpend/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,5 +12,5 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "SglPend_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "SglPend_SRS") srs printSetting
genDot fullSI
2 changes: 1 addition & 1 deletion code/drasil-example/ssp/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "SSP_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "SSP_SRS") srs printSetting
genDot fullSI
-- for when we can generate code again, uncomment this file and Choices.hs
--genCode choices code
2 changes: 1 addition & 1 deletion code/drasil-example/swhs/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ main =
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "SWHS_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "SWHS_SRS") srs printSetting
genDot fullSI
-- When ready to generate code from SWHS, uncomment this file and Choices
-- genCode choices code
Expand Down
2 changes: 1 addition & 1 deletion code/drasil-example/swhsnopcm/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,6 @@ main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
typeCheckSI fullSI
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "SWHSNoPCM_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "SWHSNoPCM_SRS") srs printSetting
genCode choices code
genDot fullSI
2 changes: 1 addition & 1 deletion code/drasil-example/template/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,4 +9,4 @@ main :: IO()
main = do
setLocaleEncoding utf8
dumpEverything fullSI printSetting ".drasil/"
gen (DocSpec (docChoices SRS [HTML, TeX, JSON]) "Template_SRS") srs printSetting
gen (DocSpec (docChoices SRS [HTML, TeX, Jupyter]) "Template_SRS") srs printSetting
40 changes: 20 additions & 20 deletions code/drasil-gen/lib/Language/Drasil/Generate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Language.Drasil.Generate (
-- * Generator Functions
gen, genDot, genCode,
-- * Types (Printing Options)
DocType(..), DocSpec(DocSpec), Format(TeX, HTML, JSON), DocChoices(DC),
DocType(..), DocSpec(DocSpec), Format(TeX, HTML, Jupyter), DocChoices(DC),
-- * Constructor
docChoices) where

Expand All @@ -23,8 +23,8 @@ import Build.Drasil (genMake)
import Language.Drasil
import Drasil.DocLang (mkGraphInfo)
import SysInfo.Drasil (SystemInformation)
import Language.Drasil.Printers (DocType(SRS, Website, Jupyter), Format(TeX, HTML, JSON),
makeCSS, genHTML, genTeX, genJSON, PrintingInformation, outputDot)
import Language.Drasil.Printers (DocType(SRS, Website, Lesson), Format(TeX, HTML, Jupyter),
makeCSS, genHTML, genTeX, genJupyter, PrintingInformation, outputDot)
import Language.Drasil.Code (generator, generateCode, Choices(..), CodeSpec(..),
Lang(..), getSampleData, readWithDataDesc, sampleInputDD,
unPP, unJP, unCSP, unCPPP, unSP)
Expand All @@ -42,21 +42,21 @@ gen ds fn sm = prnt sm ds fn -- FIXME: 'prnt' is just 'gen' with the arguments r
-- TODO: Include Jupyter into the SRS setup.
-- | Generate the output artifacts (TeX+Makefile, HTML or Notebook).
prnt :: PrintingInformation -> DocSpec -> Document -> IO ()
prnt sm (DocSpec (DC Jupyter _) fn) body =
do prntDoc body sm fn Jupyter JSON
prnt sm (DocSpec (DC Lesson _) fn) body =
do prntDoc body sm fn Lesson Jupyter
prnt sm (DocSpec (DC dtype fmts) fn) body =
do mapM_ (prntDoc body sm fn dtype) fmts

-- | Helper for writing the documents (TeX / HTML / JSON) to file.
-- | Helper for writing the documents (TeX / HTML / Jupyter) to file.
prntDoc :: Document -> PrintingInformation -> String -> DocType -> Format -> IO ()
prntDoc d pinfo fn Jupyter _ = prntDoc' Jupyter "Jupyter" fn JSON d pinfo
prntDoc d pinfo fn Lesson _ = prntDoc' Lesson "Lesson" fn Jupyter d pinfo
prntDoc d pinfo fn dtype fmt =
case fmt of
HTML -> do prntDoc' dtype (show dtype ++ "/HTML") fn HTML d pinfo
prntCSS dtype fn d
TeX -> do prntDoc' dtype (show dtype ++ "/PDF") fn TeX d pinfo
prntMake $ DocSpec (DC dtype []) fn
JSON -> do prntDoc' dtype (show dtype ++ "/JSON") fn JSON d pinfo
HTML -> do prntDoc' dtype (show dtype ++ "/HTML") fn HTML d pinfo
prntCSS dtype fn d
TeX -> do prntDoc' dtype (show dtype ++ "/PDF") fn TeX d pinfo
prntMake $ DocSpec (DC dtype []) fn
Jupyter -> do prntDoc' dtype (show dtype ++ "/Jupyter") fn Jupyter d pinfo
_ -> mempty

-- | Helper that takes the document type, directory name, document name, format of documents,
Expand All @@ -67,10 +67,10 @@ prntDoc' dt dt' fn format body' sm = do
outh <- openFile (dt' ++ "/" ++ fn ++ getExt format) WriteMode
hPutStrLn outh $ render $ writeDoc sm dt format fn body'
hClose outh
where getExt TeX = ".tex"
getExt HTML = ".html"
getExt JSON = ".ipynb"
getExt _ = error "We can only write in TeX, HTML and Jupyter Notebook (for now)."
where getExt TeX = ".tex"
getExt HTML = ".html"
getExt Jupyter = ".ipynb"
getExt _ = error "We can only write in TeX, HTML and Jupyter Notebook (for now)."

-- | Helper for writing the Makefile(s).
prntMake :: DocSpec -> IO ()
Expand All @@ -91,10 +91,10 @@ prntCSS docType fn body = do

-- | Renders the documents.
writeDoc :: PrintingInformation -> DocType -> Format -> Filename -> Document -> Doc
writeDoc s _ TeX _ doc = genTeX doc s
writeDoc s _ HTML fn doc = genHTML s fn doc
writeDoc s dt JSON _ doc = genJSON s dt doc
writeDoc _ _ _ _ _ = error "we can only write TeX/HTML/JSON (for now)"
writeDoc s _ TeX _ doc = genTeX doc s
writeDoc s _ HTML fn doc = genHTML s fn doc
writeDoc s dt Jupyter _ doc = genJupyter s dt doc
writeDoc _ _ _ _ _ = error "we can only write TeX/HTML/Jupyter (for now)"

-- | Generates traceability graphs as .dot files.
genDot :: SystemInformation -> IO ()
Expand Down
10 changes: 5 additions & 5 deletions code/drasil-printers/lib/Language/Drasil/Format.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,13 +4,13 @@ module Language.Drasil.Format where
-- | Document types include Software Requirements Specification and Website.
-- Choosing SRS will generate both TeX and HTML files, while Website generates only as HTML.
-- This also determines what folders the generated files will be placed into.
data DocType = SRS | Website | Jupyter
data DocType = SRS | Website | Lesson

-- | Possible formats for printer output.
data Format = TeX | Plain | HTML | JSON
data Format = TeX | Plain | HTML | Jupyter

-- | Shows the different types of documents.
instance Show DocType where
show Jupyter = "Jupyter"
show SRS = "SRS"
show Website = "Website"
show Lesson = "Lesson"
show SRS = "SRS"
show Website = "Website"
10 changes: 5 additions & 5 deletions code/drasil-printers/lib/Language/Drasil/JSON/Print.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,13 @@
-- | Defines .json printers to generate jupyter notebooks. For more information on each of the helper functions, please view the [source files](https://jacquescarette.github.io/Drasil/docs/full/drasil-printers-0.1.10.0/src/Language.Drasil.JSON.Print.html).
module Language.Drasil.JSON.Print(genJSON) where
module Language.Drasil.JSON.Print(genJupyter) where

import Prelude hiding (print, (<>))
import Text.PrettyPrint hiding (Str)
import Numeric (showEFloat)

import qualified Language.Drasil as L

import Language.Drasil.Format (DocType(Jupyter))
import Language.Drasil.Format (DocType(Lesson))

import Language.Drasil.Printing.Import (makeDocument)
import Language.Drasil.Printing.AST (Spec, ItemType(Flat, Nested),
Expand All @@ -32,9 +32,9 @@ import Language.Drasil.JSON.Helpers (makeMetadata, h, stripnewLine, nbformat, co
-- | Generate a python notebook document (using json).
-- build : build the SRS document in JSON format
-- build': build the general Jupyter Notbook document
genJSON :: PrintingInformation -> DocType -> L.Document -> Doc
genJSON sm Jupyter doc = build (makeDocument sm doc)
genJSON sm _ doc = build' (makeDocument sm doc)
genJupyter :: PrintingInformation -> DocType -> L.Document -> Doc
genJupyter sm Lesson doc = build (makeDocument sm doc)
genJupyter sm _ doc = build' (makeDocument sm doc)

-- | Build the JSON Document, called by genJSON
build :: Document -> Doc
Expand Down
8 changes: 4 additions & 4 deletions code/drasil-printers/lib/Language/Drasil/Printers.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
module Language.Drasil.Printers (
-- * Formats
DocType(SRS, Website, Jupyter), Format(TeX, HTML, JSON)
DocType(SRS, Website, Lesson), Format(TeX, HTML, Jupyter)
-- * DOT
-- ** Types
, GraphInfo(..), NodeFamily(..)
Expand All @@ -25,7 +25,7 @@ module Language.Drasil.Printers (
-- * TeX
, genTeX
-- * Jupyter
, genJSON
, genJupyter
-- * Log
, printAllDebugInfo
-- * Printing Information and Options
Expand All @@ -36,10 +36,10 @@ module Language.Drasil.Printers (
)
where

import Language.Drasil.Format (DocType(SRS, Website, Jupyter), Format(TeX, HTML,JSON))
import Language.Drasil.Format (DocType(SRS, Website, Lesson), Format(TeX, HTML, Jupyter))
import Language.Drasil.HTML.CSS (makeCSS)
import Language.Drasil.HTML.Print (genHTML)
import Language.Drasil.JSON.Print (genJSON)
import Language.Drasil.JSON.Print (genJupyter)
import Language.Drasil.Markdown.CreateMd (makeMd, introInfo, verInfo, unsupOS,
extLibSec, instDoc, regularSec, endNote, whatInfo)
import Language.Drasil.Plain.Print (SingleLine(..), sentenceDoc, exprDoc,
Expand Down
File renamed without changes.
File renamed without changes.
File renamed without changes.

0 comments on commit a33094f

Please sign in to comment.