├── .gitignore ├── AUTHORS ├── CHANGELOG ├── Controller.hs ├── DisplayOptions.hs ├── Editor.hs ├── Heading.hs ├── ImportExport.hs ├── Item.hs ├── LICENSE ├── Main.hs ├── Makefile ├── Paragraph.hs ├── ProofTree.hs ├── Prop.hs ├── README.org ├── ROADMAP ├── Rule.hs ├── StringRep.hs ├── SyntaxDecl.hs ├── Terms.hs ├── Unification.hs ├── View ├── Editor.hs ├── Heading.hs ├── Item.hs ├── Paragraph.hs ├── ProofTree.hs ├── Prop.hs ├── Rule.hs ├── SyntaxDecl.hs ├── Term.hs └── Utils.hs ├── app.cabal ├── browser-fs-access.min.js ├── cabal.config ├── cabal.project.local ├── cmunfonts ├── README.md ├── example.html ├── font │ ├── Bright Semibold │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-bright-semibold.css │ │ ├── cmunbso.eot │ │ ├── cmunbso.svg │ │ ├── cmunbso.ttf │ │ ├── cmunbso.woff │ │ ├── cmunbsr.eot │ │ ├── cmunbsr.svg │ │ ├── cmunbsr.ttf │ │ └── cmunbsr.woff │ ├── Bright │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-bright.css │ │ ├── cmunbbx.eot │ │ ├── cmunbbx.ttf │ │ ├── cmunbbx.woff │ │ ├── cmunbmo.eot │ │ ├── cmunbmo.ttf │ │ ├── cmunbmo.woff │ │ ├── cmunbmr.eot │ │ ├── cmunbmr.ttf │ │ ├── cmunbmr.woff │ │ ├── cmunbxo.eot │ │ ├── cmunbxo.ttf │ │ └── cmunbxo.woff │ ├── Classical Serif Italic │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-classical-serif-italic.css │ │ ├── cmunci.eot │ │ ├── cmunci.svg │ │ ├── cmunci.ttf │ │ └── cmunci.woff │ ├── Concrete │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-concrete.css │ │ ├── cmunobi.eot │ │ ├── cmunobi.svg │ │ ├── cmunobi.ttf │ │ ├── cmunobi.woff │ │ ├── cmunobx.eot │ │ ├── cmunobx.svg │ │ ├── cmunobx.ttf │ │ ├── cmunobx.woff │ │ ├── cmunorm.eot │ │ ├── cmunorm.svg │ │ ├── cmunorm.ttf │ │ ├── cmunorm.woff │ │ ├── cmunoti.eot │ │ ├── cmunoti.svg │ │ ├── cmunoti.ttf │ │ └── cmunoti.woff │ ├── OFL-FAQ.txt │ ├── OFL.txt │ ├── README.txt │ ├── Sans Demi-Condensed │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-sans-demicondensed.css │ │ ├── cmunssdc.eot │ │ ├── cmunssdc.svg │ │ ├── cmunssdc.ttf │ │ └── cmunssdc.woff │ ├── Sans │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-sans.css │ │ ├── cmunsi.eot │ │ ├── cmunsi.svg │ │ ├── cmunsi.ttf │ │ ├── cmunsi.woff │ │ ├── cmunso.eot │ │ ├── cmunso.svg │ │ ├── cmunso.ttf │ │ ├── cmunso.woff │ │ ├── cmunss.eot │ │ ├── cmunss.svg │ │ ├── cmunss.ttf │ │ ├── cmunss.woff │ │ ├── cmunsx.eot │ │ ├── cmunsx.svg │ │ ├── cmunsx.ttf │ │ └── cmunsx.woff │ ├── Serif Slanted │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-serif-slanted.css │ │ ├── cmunbl.eot │ │ ├── cmunbl.svg │ │ ├── cmunbl.ttf │ │ ├── cmunbl.woff │ │ ├── cmunsl.eot │ │ ├── cmunsl.svg │ │ ├── cmunsl.ttf │ │ └── cmunsl.woff │ ├── Serif │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-serif.css │ │ ├── cmunbi.eot │ │ ├── cmunbi.svg │ │ ├── cmunbi.ttf │ │ ├── cmunbi.woff │ │ ├── cmunbx.eot │ │ ├── cmunbx.svg │ │ ├── cmunbx.ttf │ │ ├── cmunbx.woff │ │ ├── cmunrm.eot │ │ ├── cmunrm.svg │ │ ├── cmunrm.ttf │ │ ├── cmunrm.woff │ │ ├── cmunti.eot │ │ ├── cmunti.svg │ │ ├── cmunti.ttf │ │ └── cmunti.woff │ ├── Typewriter Light │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-typewriter-light.css │ │ ├── cmunbtl.eot │ │ ├── cmunbtl.svg │ │ ├── cmunbtl.ttf │ │ ├── cmunbtl.woff │ │ ├── cmunbto.eot │ │ ├── cmunbto.svg │ │ ├── cmunbto.ttf │ │ └── cmunbto.woff │ ├── Typewriter Variable │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-typewriter-variable.css │ │ ├── cmunvi.eot │ │ ├── cmunvi.svg │ │ ├── cmunvi.ttf │ │ ├── cmunvi.woff │ │ ├── cmunvt.eot │ │ ├── cmunvt.svg │ │ ├── cmunvt.ttf │ │ └── cmunvt.woff │ ├── Typewriter │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-typewriter.css │ │ ├── cmunit.eot │ │ ├── cmunit.svg │ │ ├── cmunit.ttf │ │ ├── cmunit.woff │ │ ├── cmuntb.eot │ │ ├── cmuntb.svg │ │ ├── cmuntb.ttf │ │ ├── cmuntb.woff │ │ ├── cmuntt.eot │ │ ├── cmuntt.svg │ │ ├── cmuntt.ttf │ │ ├── cmuntt.woff │ │ ├── cmuntx.eot │ │ ├── cmuntx.svg │ │ ├── cmuntx.ttf │ │ └── cmuntx.woff │ ├── Upright Italic │ │ ├── OFL-FAQ.txt │ │ ├── OFL.txt │ │ ├── README.txt │ │ ├── cmun-upright-italic.css │ │ ├── cmunui.eot │ │ ├── cmunui.svg │ │ ├── cmunui.ttf │ │ └── cmunui.woff │ └── generator_config.txt ├── fonts.css └── fonts.scss ├── euler.woff ├── favicon.PNG ├── index.holbert ├── index.html ├── oldindex.holbert ├── split.min.js ├── typicons.eot ├── typicons.min.css ├── typicons.svg ├── typicons.ttf └── typicons.woff /.gitignore: -------------------------------------------------------------------------------- 1 | *.swp 2 | /dist 3 | /result 4 | /dist-newstyle 5 | *.local~ 6 | .DS_Store 7 | -------------------------------------------------------------------------------- /AUTHORS: -------------------------------------------------------------------------------- 1 | Liam O'Connor (l.oconnor@ed.ac.uk) 2 | Rayhana Amjad - equality and rewriting 3 | Chris Perceval-Maxwell - elimination and induction 4 | Yining Liu - multi-file documents and imports 5 | Yueyang Tang - mix-fix syntax 6 | -------------------------------------------------------------------------------- /CHANGELOG: -------------------------------------------------------------------------------- 1 | * In progress 2 | - Forward reasoning, calc proofs 3 | 4 | * Version 0.6: 5 | - New feature: Files can now be loaded directly from the local file system. 6 | - Improvement: When supported, the download/save button produces a file picker dialog. 7 | - Improvement: Can set associativity and precedence of mix-fix input syntax. 8 | - Improvement: Notation blocks can now define more than one mix-fix syntax. 9 | - Improvement: Proof style buttons condensed into hover-menu. 10 | - New feature: Summary proof display style (breaks file format) 11 | - New feature: Constructors. Identifiers that begin with '@' are assumed to be constructors, 12 | which are rendered specially, and are automatically considered to be injective 13 | and disjoint from all other constructors. Injectivity and Disjointness are 14 | automatically used when eliminating on an equality assumption where both 15 | sides are constructors. 16 | - Bug fix: Elimination rules that only refer to outer skolem variables no longer cause a crash. 17 | 18 | * Version 0.5.1 19 | - New feature: Tooltip footnotes for references and footnotes. 20 | - New feature: Links are supported in paragraphs as are images by URL. 21 | - New feature: Goal tag markup 22 | - New feature: Overline syntax from * postfix. 23 | - New feature: Embedding rules in text 24 | - New feature: Embedding rule names in text 25 | - New feature: "Reader mode" that hides buttons. 26 | - New feature: "Presentation mode" that shows one section at a time. 27 | - Improvement: Auto-rename introduced metas to avoid shadowing. 28 | - New feature: Basic mix-fix syntax notation support. 29 | 30 | * Version 0.5 31 | - Improvement: Reflexivity now auto-applied by clicking the rewrite button 32 | - New feature: Can now define multiple rules in an Axiom block 33 | - New feature: Can now define "inductive definitions" as a block of 34 | introduction rules. Cases and induction rules are then auto-generated. 35 | - Improvement: Can rewrite with local assumptions 36 | - Improvement: Unification now gives better solutions for induction rules. 37 | - Improvement: Axiom blocks can now contain multiple rules. 38 | 39 | * Version 0.4 40 | - New feature: Goal display on RHS 41 | - Improvement: Only displays applicable rules 42 | - New feature: Night mode 43 | - New feature: Prose style proofs 44 | - New feature: Apply a rule as an elimination rule 45 | - New feature: Apply an equality rule as a rewrite 46 | - Improvement: Holbert documents are now printable 47 | 48 | * Version 0.3.1 49 | - Improvement: Banished `String` representations to improve performance 50 | - Improvement: UI Performance greatly improved by not updating model on every keystroke. 51 | 52 | * Version 0.3 53 | - New feature: Can now instantiate metavariables in proofs 54 | - Improvement: Metavariables are represented numerically for efficiency. 55 | - Bug fix: Incorrect version number in HTML title 56 | 57 | * Version 0.2 58 | - New feature: Tooltips are now on all icons 59 | - New feature: Can now download documents as a JSON blob 60 | - New feature: Can now load documents from a JSON blob via XHR 61 | - Change: Now loads index.holbert on startup 62 | - Bug fix: Does not display trash can on the base conclusion of a rule. 63 | - Bug fix: Fixed font sizes for heading editors 64 | 65 | * Version 0.1 66 | Pre-release version. 67 | -------------------------------------------------------------------------------- /Controller.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE TypeFamilies, DeriveFunctor #-} 2 | module Controller where 3 | import Control.Monad.Except 4 | import Control.Monad.State 5 | import qualified Prop as P 6 | import qualified Miso.String as MS 7 | import StringRep (SyntaxTable) 8 | 9 | data FocusOutcome focus = Switch focus | Leave focus | Clear deriving (Functor) 10 | 11 | data ControllerState focus = CS 12 | { toSetFocus :: FocusOutcome focus 13 | , editing :: MS.MisoString 14 | , syntaxes :: SyntaxTable 15 | , knownRules :: [P.NamedProp] 16 | , originalFocus :: Maybe focus 17 | , invalidates :: [MS.MisoString] 18 | , renames :: [(MS.MisoString, MS.MisoString)] 19 | , newnames :: [MS.MisoString] 20 | } 21 | 22 | type Controller focus a = ExceptT MS.MisoString (State (ControllerState focus)) a 23 | 24 | runController :: Controller focus a -> MS.MisoString -> SyntaxTable -> [P.NamedProp] -> Maybe focus 25 | -> Either MS.MisoString (a, FocusOutcome focus, [MS.MisoString], [(MS.MisoString, MS.MisoString)], [MS.MisoString]) 26 | runController act ed tbl prps foc = case runState (runExceptT act) (CS Clear ed tbl prps foc [] [] []) of 27 | (Right a, CS f _ _ _ _ iv rn nn) -> Right (a, f, iv, rn, nn) 28 | (Left e, _) -> Left e 29 | 30 | errorMessage :: MS.MisoString -> Controller focus a 31 | errorMessage str = throwError str 32 | 33 | clearFocus :: Controller focus () 34 | clearFocus = modify (\(CS ff txt sy prps foc inv rn nn) -> CS Clear txt sy prps foc inv rn nn) 35 | 36 | setFocusWithLeaving :: focus -> Controller focus () 37 | setFocusWithLeaving f = modify (\(CS ff txt sy prps foc inv rn nn) -> CS (Leave f) txt sy prps foc inv rn nn) 38 | 39 | 40 | setFocus :: focus -> Controller focus () 41 | setFocus f = modify (\(CS ff txt sy prps foc inv rn nn) -> CS (Switch f) txt sy prps foc inv rn nn) 42 | 43 | getOriginalFocus :: Controller focus (Maybe focus) 44 | getOriginalFocus = originalFocus <$> get 45 | 46 | getKnownRules :: Controller focus [P.NamedProp] 47 | getKnownRules = knownRules <$> get 48 | 49 | textInput :: Controller focus MS.MisoString 50 | textInput = editing <$> get 51 | 52 | syntaxTable :: Controller focus SyntaxTable 53 | syntaxTable = syntaxes <$> get 54 | 55 | anyInvalidated :: Controller focus Bool 56 | anyInvalidated = not . null . invalidates <$> get 57 | 58 | invalidate :: MS.MisoString -> Controller focus () 59 | invalidate n = modify (\(CS ff txt sy prps foc inv rn nn) -> (CS ff txt sy prps foc (n : inv) rn nn)) 60 | 61 | renameResource :: MS.MisoString -> MS.MisoString -> Controller focus () 62 | renameResource n m = modify (\(CS ff txt sy prps foc inv rn nn) -> (CS ff txt sy prps foc inv ((n, m) : rn) nn)) 63 | 64 | newResource :: MS.MisoString -> Controller focus () 65 | newResource n = modify (\(CS ff txt sy prps foc inv rn nn) -> (CS ff txt sy prps foc inv rn (n:nn))) 66 | 67 | 68 | zoomFocus :: (focus -> focus') -> (focus' -> Maybe focus) -> Controller focus a -> Controller focus' a 69 | zoomFocus f f' act = do 70 | CS sf ed sy prps foc inv rn nn <- get 71 | case runState (runExceptT act) (CS Clear ed sy prps (f' =<< foc) inv rn nn) of 72 | (Left e, _) -> errorMessage e 73 | (Right a, (CS sf' ed' sy' prps' foc' inv' rn' nn')) -> put (CS (fmap f sf') ed' sy' prps' (fmap f foc') inv' rn' nn') >> pure a 74 | 75 | noFocus :: Controller focus a -> Controller () a 76 | noFocus = zoomFocus (const ()) (const Nothing) 77 | 78 | class Control s where 79 | data Action s 80 | data Focus s 81 | handle :: Action s -> s -> Controller (Focus s) s 82 | leaveFocus :: Focus s -> s -> Controller () s 83 | editable :: SyntaxTable -> Focus s -> s -> Maybe MS.MisoString 84 | invalidated :: MS.MisoString -> s -> s 85 | invalidated = const id 86 | renamed :: (MS.MisoString, MS.MisoString) -> s -> s 87 | renamed = const id 88 | defined :: s -> [P.NamedProp] 89 | defined = const [] 90 | inserted :: s -> Focus s 91 | definedSyntax :: s -> SyntaxTable 92 | definedSyntax = const [] -------------------------------------------------------------------------------- /DisplayOptions.hs: -------------------------------------------------------------------------------- 1 | module DisplayOptions where 2 | 3 | data DisplayOptions = O 4 | { showMetaBinders :: Bool 5 | , assumptionsMode :: AssumptionsMode 6 | , compactRules :: RuleStyle 7 | , tDOs :: TermDisplayOptions 8 | } deriving (Show, Eq) 9 | 10 | data TermDisplayOptions = TDO {showTeles :: Bool, showInfixes :: Bool} 11 | deriving (Show, Eq) 12 | 13 | data RuleStyle = BarTurnstile | Turnstile | Bar | Dots 14 | deriving (Show, Eq) 15 | 16 | data AssumptionsMode = Cumulative | New | Hidden 17 | deriving (Show, Eq) -------------------------------------------------------------------------------- /Editor.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings #-} 2 | {-# LANGUAGE RankNTypes #-} 3 | {-# LANGUAGE TypeFamilies #-} 4 | {-# LANGUAGE BangPatterns #-} 5 | module Editor where 6 | import Data.Maybe (fromJust, fromMaybe,mapMaybe) 7 | import qualified Miso.String as MS 8 | import Optics.Core 9 | import Control.Monad (foldM) 10 | import Controller 11 | import qualified Heading as H 12 | import qualified Item as I 13 | import qualified Paragraph as P 14 | import qualified ProofTree as PT 15 | import qualified SyntaxDecl as S 16 | import qualified StringRep as SR 17 | import qualified Prop as Prp 18 | import qualified Rule as R 19 | import DisplayOptions 20 | import qualified Data.Char 21 | import Debug.Trace 22 | type Document = [I.Item] 23 | type ItemIndex = Int 24 | 25 | type InputText = MS.MisoString 26 | type ErrorMessage = MS.MisoString 27 | 28 | data Editor = Editor 29 | { document :: Document 30 | , currentFocus :: EditorFocus 31 | , inputText :: InputText 32 | , message :: Maybe ErrorMessage 33 | , displayOptions :: DisplayOptions 34 | , presentation :: Maybe (Int, Int) 35 | , readerMode :: Bool 36 | } deriving (Show, Eq) 37 | 38 | data EditorFocus 39 | = ItemFocus ItemIndex (Focus I.Item) 40 | | NoFocus 41 | | NewItemFocus ItemIndex 42 | | InsertingPropositionFocus R.RuleType ItemIndex 43 | -- | InsertingSyntaxDeclFocus ItemIndex 44 | | CreditsFocus 45 | | ImportFocus 46 | deriving (Show, Eq) 47 | 48 | data EditorAction 49 | = SetFocus EditorFocus 50 | | ItemAction (Maybe ItemIndex) (Action I.Item) 51 | | ChangeDisplayOptions DisplayOptions 52 | | Noop 53 | | Reset 54 | | ShiftDown ItemIndex 55 | | DeleteItem ItemIndex 56 | | NewItemMenu ItemIndex 57 | | UpdateInput MS.MisoString 58 | | InsertItem ItemIndex I.Item 59 | | InsertProposition ItemIndex R.RuleType 60 | -- | InsertSyntaxDecl ItemIndex 61 | | Download 62 | | Upload 63 | | Import 64 | | LoadDocument Document 65 | | DisplayError MS.MisoString 66 | | EnterPresentation 67 | | ExitPresentation 68 | | NextSlide 69 | | PrevSlide 70 | | ToggleReader 71 | deriving (Show, Eq) 72 | 73 | initialEditor :: MS.MisoString -> Editor 74 | initialEditor url = 75 | Editor [I.Heading $ H.Heading 4 "Loading..."] NoFocus url Nothing (O True New BarTurnstile (TDO False True)) Nothing False 76 | 77 | after :: Int -> AffineTraversal' [a] (a, [a]) 78 | after n = atraversalVL guts 79 | where 80 | guts :: AffineTraversalVL' [a] (a, [a]) 81 | guts pure' act ls = 82 | let (lefts, itrights) = splitAt n ls 83 | in case itrights of 84 | (it : rights) -> 85 | (\(it', rights') -> lefts ++ it' : rights') <$> act (it, rights) 86 | _ -> pure' ls 87 | 88 | 89 | 90 | getRuleAt :: Int -> Document -> R.Rule 91 | getRuleAt i s = case s !! i of 92 | I.Rule v -> v 93 | _ -> error "Rule not found!" 94 | 95 | processNewnames :: [MS.MisoString] -> Document -> Either MS.MisoString () 96 | processNewnames nn doc = mapM_ processNewname nn 97 | where 98 | processNewname n = case n of 99 | "" -> Left "Name cannot be empty" 100 | _ | n `elem` concatMap (mapMaybe (Prp.defnName . fst) . defined) doc -> Left "Name already in use" 101 | | otherwise -> Right () 102 | 103 | processRenames :: [(MS.MisoString, MS.MisoString)] -> Document -> Either MS.MisoString Document 104 | processRenames rns doc = foldM processRename doc rns 105 | where 106 | names = mapMaybe (Prp.defnName . fst) $ concatMap defined doc 107 | processRename doc (s, s') 108 | | s' `elem` names = Left "Cannot rename: Name already in use" 109 | | otherwise = Right $ map (renamed (s, s')) doc 110 | 111 | switchFocus :: EditorFocus -> Editor -> Editor 112 | switchFocus (ItemFocus idx f) ed = 113 | let (lefts, x : rest) = splitAt idx (document ed) 114 | in ed 115 | { currentFocus = ItemFocus idx f 116 | , inputText = fromMaybe "" (editable (concatMap definedSyntax lefts) f x) 117 | } 118 | switchFocus f ed = ed {currentFocus = f, inputText = ""} 119 | 120 | runAction :: EditorAction -> Editor -> Editor 121 | runAction act ed = case runAction' act ed of 122 | Left e -> ed {message = Just e} 123 | Right ed' -> ed' 124 | 125 | runAction' :: EditorAction -> Editor -> Either MS.MisoString Editor 126 | runAction' Noop ed = pure ed 127 | runAction' Reset ed = pure (ed {message = Nothing, currentFocus = NoFocus}) 128 | runAction' (ItemAction mi act) ed = do 129 | let index | Just i <- mi = i 130 | | ItemFocus i _ <- currentFocus ed = i 131 | let localFocus = case currentFocus ed of 132 | ItemFocus i' f | i' == index -> Just f 133 | _ -> Nothing 134 | let (lefts,it:rights) = splitAt index (document ed) 135 | (item, mf, inv, rns, nn) <- runController (handle act it) (inputText ed) (concatMap definedSyntax lefts) (concatMap defined lefts) localFocus 136 | processNewnames nn (document ed) 137 | doc' <- processRenames rns (document ed) 138 | let doc'' = over (after index) (\(_, rest) -> (item, map (foldr (.) id (map invalidated inv)) rest)) doc' 139 | ed' = ed {message = Nothing, document = doc''} 140 | (leave, newFocus) = case mf of 141 | Clear -> (False, NoFocus) 142 | Switch f -> (False, ItemFocus index f) 143 | Leave f -> (True, ItemFocus index f) 144 | (if leave then runAction' (SetFocus newFocus) else (pure . switchFocus newFocus)) ed' 145 | runAction' (SetFocus f) ed = case currentFocus ed of 146 | ItemFocus i f' -> do 147 | let (lefts,it:rights) = splitAt i (document ed) 148 | (item, _, inv, rns, nn) <- runController (leaveFocus f' it) (inputText ed) (concatMap definedSyntax lefts) (concatMap defined lefts) (Just ()) 149 | processNewnames nn (document ed) 150 | doc' <- processRenames rns (document ed) 151 | let doc = over (after i) (\(_, rest) -> (item, map (foldr (.) id (map invalidated inv)) rest)) doc' 152 | Right $ switchFocus f (ed {message = Nothing, document = doc}) 153 | _ -> Right $ switchFocus f (ed {message = Nothing}) 154 | 155 | runAction' (ChangeDisplayOptions opts) ed = pure (ed {displayOptions = opts}) 156 | runAction' (UpdateInput s) ed = pure (ed {inputText = s}) 157 | 158 | runAction' (InsertItem idx itm) ed = 159 | let (first, last) = splitAt (idx + 1) (document ed) 160 | in pure $ switchFocus (ItemFocus (idx + 1) $ inserted itm) $ ed 161 | { document = first ++ itm : last, message = Nothing } 162 | 163 | runAction' (ShiftDown idx) ed = 164 | let (lefts, x : y : rest) = splitAt idx (document ed) 165 | y' = foldr (.) id (map (maybe id invalidated . Prp.defnName . fst) (defined x)) y 166 | in pure (ed {document = lefts ++ y' : x : rest, currentFocus = NoFocus, message = Nothing}) 167 | 168 | runAction' (DeleteItem idx) ed = 169 | let (lefts, x : rest) = splitAt idx (document ed) 170 | rest' = map (foldr (.) id (map (maybe id invalidated . Prp.defnName . fst) (defined x))) rest 171 | in pure (ed {document = lefts ++ rest', currentFocus = NoFocus, message = Nothing}) 172 | 173 | runAction' (InsertProposition idx ruleType) ed = 174 | let n = inputText ed 175 | item = R.blank ruleType n 176 | in case n of 177 | "" -> Left "Name cannot be empty" 178 | _ | MS.all Data.Char.isSpace n -> Left "Name cannot be empty" 179 | _ | n `elem` concatMap (mapMaybe (Prp.defnName . fst) . defined) (document ed) -> Left "Name already in use" 180 | _ -> runAction' (InsertItem idx (I.Rule item)) ed 181 | 182 | runAction' EnterPresentation ed = Right $ ed { presentation = Just (nextSlide (document ed) (0,0)) } 183 | runAction' ExitPresentation ed = Right $ ed { presentation = Nothing } 184 | runAction' NextSlide ed = case presentation ed of 185 | Nothing -> Right $ ed 186 | Just i -> Right $ ed { presentation = Just (nextSlide (document ed) i) } 187 | runAction' PrevSlide ed = case presentation ed of 188 | Nothing -> Right $ ed 189 | Just i -> Right $ ed { presentation = Just (prevSlide (document ed) i) } 190 | runAction' (LoadDocument m) ed = Right $ ed { document = migrate m, currentFocus = NoFocus, message = Nothing} 191 | where migrate = id -- map (\i -> over (I.rule % R.ruleItems % R.proofState % R.proofTree % PT.ruleRefs) (\ x -> case x of Prp.OldRewrite a b -> Prp.Rewrite a b Nothing; y -> y) i) 192 | runAction' (ToggleReader) ed = Right $ ed { readerMode = not (readerMode ed) } 193 | runAction' (DisplayError e) ed = Left e 194 | 195 | 196 | nextSlide :: Document -> (Int, Int) -> (Int, Int) 197 | nextSlide d (start,end) | end >= length d = (start, end) 198 | nextSlide d (start,end) = case stepTillHeading 1 (end+1) (drop (end +1) d) of 199 | Just i -> if i <= end then (start,end) else (end, i) 200 | Nothing -> (start,end) 201 | 202 | prevSlide :: Document -> (Int, Int) -> (Int, Int) 203 | prevSlide d (0,end) = (0,end) 204 | prevSlide d (start,end) = case stepTillHeading (-1) start (reverse $ take start d) of 205 | Just i -> if (start <= i-1) then (start,end) else (i-1, start) 206 | Nothing -> (start,end) 207 | 208 | stepTillHeading :: Int -> Int -> Document -> Maybe Int 209 | stepTillHeading sp (!n) (I.Heading (H.Heading i _):rest) | i <= 1 = Just n 210 | stepTillHeading sp (!n) (x:rest) = stepTillHeading sp (n + sp) rest 211 | stepTillHeading sp (!n) [] = Just n 212 | -------------------------------------------------------------------------------- /Heading.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE TypeFamilies, DeriveAnyClass, DeriveGeneric #-} 2 | module Heading where 3 | import Controller 4 | import Miso.String 5 | import GHC.Generics(Generic) 6 | import Data.Aeson (ToJSON,FromJSON) 7 | 8 | data Heading = Heading Int MisoString 9 | deriving (Show, Eq, Generic, ToJSON, FromJSON) 10 | 11 | instance Control Heading where 12 | data Focus Heading = Select 13 | deriving (Show, Eq) 14 | data Action Heading = Edit 15 | deriving (Show, Eq) 16 | 17 | editable _ Select (Heading i s) = Just s 18 | 19 | leaveFocus _ = pure 20 | 21 | handle Edit (Heading i _) = Heading i <$> textInput 22 | 23 | inserted _ = Select -------------------------------------------------------------------------------- /ImportExport.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings #-} 2 | {-# LANGUAGE JavaScriptFFI #-} 3 | module ImportExport where 4 | -- Vandelay Industries 5 | import Miso 6 | import Data.JSString 7 | import JavaScript.Web.XMLHttpRequest 8 | import Data.Aeson 9 | import GHCJS.Marshal 10 | import qualified Control.Exception as Exc 11 | 12 | 13 | cleanup :: IO a -> IO (Maybe a) 14 | cleanup x = Exc.catch (Just <$> x) handler 15 | where 16 | handler exc = return Nothing `const` (exc :: Exc.ErrorCall) 17 | 18 | import_ :: (FromJSON a) => JSString -> IO (Either JSString a) 19 | import_ url = do 20 | response <- xhr $ Request GET url Nothing [] False NoData 21 | case status response of 22 | 200 -> 23 | case contents response of 24 | Nothing -> pure $ Left "empty response" 25 | Just s -> do 26 | s' <- cleanup . parse =<< toJSVal (s :: JSString) 27 | pure $ case s' of 28 | Nothing -> Left "cannot parse file" 29 | Just r -> Right r 30 | _ -> pure $ Left "Unsuccessful status code" 31 | 32 | export :: (ToJSON a) => JSString -> a -> IO () 33 | export fn m = stringify m >>= saveAs fn 34 | 35 | openFile :: (FromJSON a) => IO (Either JSString a) 36 | openFile = do 37 | str <- fileOpenHelper 38 | s' <- cleanup . parse =<< toJSVal (str :: JSString) 39 | pure $ case s' of 40 | Nothing -> Left "cannot parse file" 41 | Just r -> Right r 42 | 43 | foreign import javascript interruptible 44 | "fileSave(new Blob([$2],{type:'application/json'}),{fileName:$1,extensions:['.holbert']}).then($c);" 45 | saveAs :: JSString -> JSString -> IO () 46 | foreign import javascript interruptible 47 | "fileOpenHelper().then($c);" 48 | fileOpenHelper :: IO JSString 49 | -------------------------------------------------------------------------------- /Item.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE TypeFamilies, DeriveGeneric, DeriveAnyClass #-} 2 | module Item where 3 | 4 | import qualified Rule as R 5 | import qualified Heading as H 6 | import qualified Paragraph as P 7 | import qualified SyntaxDecl as S 8 | import Controller 9 | import GHC.Generics(Generic) 10 | import Data.Aeson (ToJSON,FromJSON) 11 | import Optics.Core 12 | 13 | data Item = Rule R.Rule 14 | | Heading H.Heading 15 | | Paragraph P.Paragraph 16 | | SyntaxDecl S.SyntaxDecl 17 | deriving (Show, Eq, Generic, ToJSON, FromJSON) 18 | 19 | 20 | rule :: Prism' Item R.Rule 21 | rule = prism Rule $ \ x -> 22 | case x of 23 | Rule r -> Right r 24 | _ -> Left x 25 | 26 | 27 | heading :: Prism' Item H.Heading 28 | heading = prism Heading $ \ x -> 29 | case x of 30 | Heading r -> Right r 31 | _ -> Left x 32 | 33 | 34 | paragraph :: Prism' Item P.Paragraph 35 | paragraph = prism Paragraph $ \ x -> 36 | case x of 37 | Paragraph r -> Right r 38 | _ -> Left x 39 | 40 | syntaxdecl :: Prism' Item S.SyntaxDecl 41 | syntaxdecl = prism SyntaxDecl $ \ x -> 42 | case x of 43 | SyntaxDecl r -> Right r 44 | _ -> Left x 45 | 46 | instance Control Item where 47 | data Action Item = RuleAct (Action R.Rule) 48 | | HeadingAct (Action H.Heading) 49 | | ParagraphAct (Action P.Paragraph) 50 | | SyntaxDeclAct (Action S.SyntaxDecl) 51 | deriving (Show, Eq) 52 | 53 | data Focus Item = RuleFocus (Focus R.Rule) 54 | | HeadingFocus (Focus H.Heading) 55 | | ParagraphFocus (Focus P.Paragraph) 56 | | SyntaxDeclFocus (Focus S.SyntaxDecl) 57 | deriving (Show, Eq) 58 | 59 | 60 | renamed n (Heading i) = Heading $ renamed n i 61 | renamed n (Rule i) = Rule $ renamed n i 62 | renamed n (Paragraph i) = Paragraph $ renamed n i 63 | renamed n (SyntaxDecl i) = SyntaxDecl $ renamed n i 64 | 65 | defined (Heading i) = defined i 66 | defined (Rule i) = defined i 67 | defined (Paragraph i) = defined i 68 | defined (SyntaxDecl i) = defined i 69 | 70 | definedSyntax (Heading i) = definedSyntax i 71 | definedSyntax (Rule i) = definedSyntax i 72 | definedSyntax (Paragraph i) = definedSyntax i 73 | definedSyntax (SyntaxDecl i) = definedSyntax i 74 | 75 | invalidated n (Heading i) = Heading $ invalidated n i 76 | invalidated n (Rule i) = Rule $ invalidated n i 77 | invalidated n (Paragraph i) = Paragraph $ invalidated n i 78 | invalidated n (SyntaxDecl i) = SyntaxDecl $ invalidated n i 79 | 80 | editable tbl (HeadingFocus f) (Heading h) = editable tbl f h 81 | editable tbl (RuleFocus f) (Rule h) = editable tbl f h 82 | editable tbl (ParagraphFocus f) (Paragraph h) = editable tbl f h 83 | editable tbl (SyntaxDeclFocus f) (SyntaxDecl h) = editable tbl f h 84 | 85 | leaveFocus (HeadingFocus f) (Heading h) = Heading <$> leaveFocus f h 86 | leaveFocus (ParagraphFocus f) (Paragraph h) = Paragraph <$> leaveFocus f h 87 | leaveFocus (RuleFocus f) (Rule h) = Rule <$> leaveFocus f h 88 | leaveFocus (SyntaxDeclFocus f) (SyntaxDecl h) = SyntaxDecl <$> leaveFocus f h 89 | 90 | handle (HeadingAct a) (Heading s) = fmap Heading . zoomFocus HeadingFocus (\x -> case x of (HeadingFocus f) -> Just f; _ -> Nothing) $ handle a s 91 | handle (ParagraphAct a) (Paragraph s) = fmap Paragraph . zoomFocus ParagraphFocus (\x -> case x of (ParagraphFocus f) -> Just f; _ -> Nothing) $ handle a s 92 | handle (RuleAct a) (Rule s) = fmap Rule . zoomFocus RuleFocus (\x -> case x of (RuleFocus f) -> Just f; _ -> Nothing) $ handle a s 93 | handle (SyntaxDeclAct a) (SyntaxDecl s) = fmap SyntaxDecl . zoomFocus SyntaxDeclFocus (\x -> case x of (SyntaxDeclFocus f) -> Just f; _ -> Nothing) $ handle a s 94 | 95 | inserted (Heading s) = HeadingFocus (inserted s) 96 | inserted (Paragraph s) = ParagraphFocus (inserted s) 97 | inserted (Rule s) = RuleFocus (inserted s) 98 | inserted (SyntaxDecl s) = SyntaxDeclFocus (inserted s) 99 | -------------------------------------------------------------------------------- /LICENSE: -------------------------------------------------------------------------------- 1 | Copyright (c) 2021, Holbert Contributors (see AUTHORS) 2 | All rights reserved. 3 | 4 | Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: 5 | 6 | 1. Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. 7 | 8 | 2. Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. 9 | 10 | 3. Neither the name of the copyright holder nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. 11 | 12 | THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT HOLDER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. 13 | -------------------------------------------------------------------------------- /Main.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE RecordWildCards, OverloadedStrings #-} 2 | module Main where 3 | import Miso 4 | import Miso.String(MisoString) 5 | import Editor (runAction, EditorAction (..), Editor (..), initialEditor) 6 | import qualified ImportExport 7 | import View.Editor (viewEditor) 8 | 9 | 10 | foreign import javascript unsafe "$r = document.location.search.slice(1);" 11 | urlparameter :: IO MisoString 12 | 13 | main :: IO () 14 | main = do 15 | url <- (\x -> if x == "" then "index.holbert" else x) <$> urlparameter 16 | startApp App {model = initialEditor url, ..} 17 | where 18 | initialAction = Import 19 | update = updateModel 20 | view = viewEditor 21 | events = defaultEvents 22 | subs = [] 23 | mountPoint = Nothing 24 | logLevel = Off 25 | 26 | updateModel :: EditorAction -> Editor -> Effect EditorAction Editor 27 | updateModel Import = \m -> act m #> m 28 | where 29 | act m = do 30 | x <- ImportExport.import_ (inputText m) 31 | pure $ case x of 32 | Left e -> DisplayError e 33 | Right x -> LoadDocument x 34 | updateModel Upload = \m -> act m #> m 35 | where 36 | act m = do 37 | x <- ImportExport.openFile 38 | pure $ case x of 39 | Left e -> DisplayError e 40 | Right x -> LoadDocument x 41 | updateModel Download = \m -> act m #> m 42 | where act m = ImportExport.export "file.holbert" (document m) >> pure Noop 43 | updateModel act = noEff . runAction act 44 | -------------------------------------------------------------------------------- /Makefile: -------------------------------------------------------------------------------- 1 | OUTPUT=dist/build/app/app.jsexe/ 2 | OUTPUT_NEWSTYLE=dist-newstyle/build/x86_64-linux/ghcjs-8.6.0.1/holbert-0.6/x/app/build/app/app.jsexe/ 3 | STATICS=index.html favicon.PNG euler.woff typicons.* *.min.js cmunfonts *.holbert 4 | all: 5 | cabal build && cp -R $(STATICS) $(OUTPUT) 6 | newstyle: 7 | cabal build && cp -R $(STATICS) $(OUTPUT_NEWSTYLE) 8 | server: 9 | cd $(OUTPUT) && python3 -m http.server 10 | server_newstyle: 11 | cd $(OUTPUT_NEWSTYLE) && python3 -m http.server 12 | launch: server_newstyle 13 | -------------------------------------------------------------------------------- /Paragraph.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE TypeFamilies, DeriveGeneric, DeriveAnyClass #-} 2 | module Paragraph where 3 | import Miso.String 4 | import Controller 5 | import GHC.Generics(Generic) 6 | import Data.Aeson (ToJSON,FromJSON) 7 | data Paragraph = Paragraph MisoString deriving (Show, Eq, Generic, ToJSON, FromJSON) 8 | 9 | instance Control Paragraph where 10 | data Focus Paragraph = Select 11 | deriving (Show, Eq) 12 | data Action Paragraph = Edit 13 | deriving (Show, Eq) 14 | 15 | editable tbl Select (Paragraph s) = Just s 16 | 17 | leaveFocus _ = pure 18 | 19 | handle Edit _ = Paragraph <$> textInput 20 | 21 | inserted _ = Select 22 | -------------------------------------------------------------------------------- /Prop.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE TupleSections, FlexibleContexts, GADTs, DeriveAnyClass, DeriveGeneric, OverloadedStrings #-} 2 | module Prop where 3 | import Unification 4 | import qualified StringRep as SR 5 | import Miso.String(MisoString) 6 | import qualified Miso.String as MS 7 | import qualified Terms as T 8 | import GHC.Generics(Generic) 9 | import Data.Aeson (ToJSON,FromJSON) 10 | import Data.Maybe (fromJust,mapMaybe) 11 | import Optics.Indexed.Core 12 | import Optics.IxAffineTraversal 13 | import Optics.Lens 14 | import Optics.Iso 15 | import Optics.Core 16 | import Control.Applicative 17 | import Data.List(foldl',elemIndex) 18 | 19 | type RuleName = MisoString 20 | 21 | data CalcLocation = LHS | RHS 22 | deriving (Eq, Show, Generic, ToJSON, FromJSON) 23 | 24 | data RuleRef = Defn RuleName 25 | | Local Int 26 | | Cases MisoString Int 27 | | Induction MisoString Int 28 | -- Built in laws 29 | | Refl 30 | | Transitivity 31 | | Distinctness RuleRef 32 | | Injectivity 33 | -- below are for presentation only in proofs 34 | | Rewrite RuleRef Bool (Maybe CalcLocation) -- bool is if it is flipped 35 | | Elim RuleRef RuleRef 36 | deriving (Eq, Show, Generic, ToJSON, FromJSON) 37 | 38 | defnName :: RuleRef -> Maybe RuleName 39 | defnName v = case v of 40 | Defn n -> Just n 41 | Cases s i -> Just $ "§cases-" <> s <> "§" <> MS.pack (show i) 42 | Induction s i -> Just $ "§induction-" <> s <> "§" <> MS.pack (show i) 43 | _ -> Nothing 44 | 45 | builtInRefl :: NamedProp 46 | builtInRefl = (Refl, Forall ["x"] [] (T.applyApTelescope (T.Const "_=_" False) [T.LocalVar 0, T.LocalVar 0])) 47 | 48 | type NamedProp = (RuleRef, Prop) 49 | data Prop = Forall [T.Name] [Prop] T.Term deriving (Eq, Ord, Show, Generic, ToJSON, FromJSON) 50 | 51 | type Path = [Int] 52 | 53 | type RuleContext = [T.Name] 54 | 55 | infixl 9 %. 56 | (%.) a b = icompose (flip (++)) (a % b) 57 | 58 | premise :: Int -> IxAffineTraversal' RuleContext Prop Prop 59 | premise n = premises % ix n 60 | 61 | path :: [Int] -> IxAffineTraversal' RuleContext Prop Prop 62 | path [] = iatraversal (Right . ([],)) (const id) 63 | path (x:xs) = path xs %. premise x 64 | 65 | premises :: IxLens' RuleContext Prop [Prop] 66 | premises = ilens (\(Forall xs lcls _) -> (reverse xs, lcls)) 67 | (\(Forall xs _ t) lcls -> Forall xs lcls t) 68 | 69 | conclusion :: IxLens' RuleContext Prop T.Term 70 | conclusion = ilens (\(Forall xs _ t) -> (reverse xs, t)) 71 | (\(Forall xs lcls _) t -> Forall xs lcls t) 72 | 73 | metabinders :: Lens' Prop [T.Name] 74 | metabinders = lens (\(Forall xs _ _) -> xs) 75 | (\(Forall _ lcls t) xs -> Forall xs lcls t) 76 | 77 | blank :: Prop 78 | blank = Forall [] [] (T.Const "???" False) 79 | 80 | removePremise :: Int -> Prop -> Prop 81 | removePremise i (Forall vs lcls g) = let (first,_:rest) = splitAt i lcls 82 | in Forall vs (first ++ rest) g 83 | 84 | addBinders :: [T.Name] -> Prop -> Prop 85 | addBinders news prop = foldl' (flip addBinder) prop news 86 | addBinder :: T.Name -> Prop -> Prop 87 | addBinder new (Forall vs lcls g) = Forall (vs ++ [new]) (map (raise 1) lcls) (T.raise 1 g) 88 | 89 | isBinderUsed :: Int -> Prop -> Bool 90 | isBinderUsed x (Forall vs lcls g) = let 91 | dbi = length vs - x - 1 92 | used = T.isUsed dbi g || any (isUsed dbi) lcls 93 | in used 94 | 95 | removeBinder :: Int -> Prop -> Prop 96 | removeBinder x (Forall vs lcls g) = let 97 | dbi = length vs - x - 1 98 | (first,_:last) = splitAt x vs 99 | g' = T.subst (T.Const "???" False) dbi g 100 | lcls' = map (subst (T.Const "???" False) dbi) lcls 101 | in Forall (first ++ last) lcls' g' 102 | 103 | isUsed :: Int -> Prop -> Bool 104 | isUsed x (Forall vs lcls g) = T.isUsed (x + length vs) g || any (isUsed (x + length vs)) lcls 105 | 106 | raise :: Int -> Prop -> Prop 107 | raise = raise' 0 108 | 109 | raise' :: Int -> Int -> Prop -> Prop 110 | raise' l n (Forall xs ps g) = Forall xs (map (raise' (l + length xs) n) ps) (T.raise' (l + length xs) n g ) 111 | 112 | subst :: T.Term -> Int -> Prop -> Prop 113 | subst t n (Forall xs rls g) = let 114 | t' = T.raise (length xs) t 115 | n' = n + length xs 116 | rls' = map (subst t' n') rls 117 | g' = T.subst t' n' g 118 | in Forall xs rls' g' 119 | 120 | -- we do no raising because substitutions should only map metavariables to closed terms 121 | applySubst :: T.Subst -> Prop -> Prop 122 | applySubst subst (Forall vs lcls g) = Forall vs (map (applySubst subst) lcls) (T.applySubst subst g) 123 | 124 | -- A bit disappointing that this can't be cleanly lensified. 125 | getConclusionString :: SR.SyntaxTable -> Path -> Prop -> MisoString 126 | getConclusionString tbl p prp = let (ctx, trm) = fromJust (ipreview (path p %. conclusion) prp) 127 | in SR.prettyPrint tbl ctx trm 128 | 129 | setConclusionString :: SR.SyntaxTable -> Path -> MisoString -> Prop -> Either MisoString Prop 130 | setConclusionString tbl p txt prp = iatraverseOf (path p %. conclusion) Right parse prp 131 | where 132 | parse ctx _ = SR.parse tbl ctx txt 133 | 134 | inductionRule :: MisoString -> Int -> [(MisoString, Int)] -> [Prop] -> NamedProp 135 | inductionRule str i formers cases = 136 | let subgoals = map caseSubgoal cases 137 | names' = map (\i -> "§" <> MS.pack (show i)) (take i [0..]) 138 | Just ii = elemIndex (str,i) formers 139 | elimAsm = T.applyApTelescope (T.Const str False) (map T.LocalVar $ reverse [0..i-1]) 140 | conclusion = T.applyApTelescope (T.LocalVar $ i + ii) (map T.LocalVar $ reverse [0..i-1]) 141 | names'' = map (\i -> "§P" <> MS.pack (show i)) (take (length formers) [0..]) 142 | in (Induction str i, Forall (names'' ++ names') (Forall [] [] elimAsm:subgoals) conclusion) 143 | where 144 | caseSubgoal (Forall vs sgs t) 145 | | (T.Const k con, rest) <- T.peelApTelescope t , Just ii <- elemIndex (k,length rest) formers 146 | = let newConc = T.applyApTelescope (T.LocalVar (length vs + i + ii)) rest 147 | sgs' = mapMaybe (eachSubgoal (length vs)) sgs 148 | eachSubgoal offset (Forall vvs sggs tt) 149 | | (T.Const kk kon, sgRest) <- T.peelApTelescope tt 150 | , Just iii <- elemIndex (kk, length sgRest) formers 151 | = let sggs' = mapMaybe (eachSubgoal $ offset + length vvs) sggs 152 | in Just (Forall vvs (sggs' ++ sggs) $ T.applyApTelescope (T.LocalVar (length vvs + offset + i + iii)) sgRest) 153 | eachSubgoal _ _ = Nothing 154 | in (Forall vs (sgs' ++ sgs) newConc) 155 | | otherwise = error "Not valid introduction rule" 156 | 157 | caseRule :: MisoString -> Int -> [Prop] -> NamedProp 158 | caseRule str i cases = 159 | let (names, subgoals) = foldr (\c (names,r) -> let (names', r') = caseSubgoal c in (merge names names', r':r)) 160 | (replicate i Nothing,[]) cases 161 | names' = zipWith (\i mn -> maybe ("§" <> MS.pack (show i)) id mn) [0..] names 162 | elimAsm = T.applyApTelescope (T.Const str False) (map T.LocalVar $ reverse [0..i-1]) 163 | in (Cases str i, Forall ("§P":names') (Forall [] [] elimAsm:subgoals) (T.LocalVar i)) 164 | where 165 | merge = zipWith (<|>) 166 | caseSubgoal (Forall vs sgs t) 167 | | (T.Const k con, rest) <- T.peelApTelescope t , length rest == i, k == str 168 | = let (sgs', vs', rest',names) = formatArgs vs rest sgs (i-1) 169 | in (names, Forall vs' sgs' (T.LocalVar (length vs' + i))) 170 | | otherwise = error "Not valid introduction rule" 171 | 172 | formatArgs vs [] sgs i = (sgs,vs,[],[]) 173 | formatArgs vs (a:as) sgs i 174 | = case a of 175 | T.LocalVar n | n < length vs 176 | -> let (lefts,name:rights) = splitAt (length vs - n-1) vs 177 | vs' = lefts ++ rights 178 | a' = T.LocalVar (i + length vs') 179 | (sgs', vs'', as',names) = formatArgs vs' (map (T.subst a' n) as) (map (subst a' n) sgs) (i-1) 180 | in (sgs', vs'', T.LocalVar (i + length vs''):as', Just name:names) 181 | _ -> let (sgs', vs', as',names) = formatArgs vs as sgs (i-1) 182 | sg = Forall [] [] $ T.Ap (T.Ap (T.Const "_=_" False) (T.LocalVar (i + length vs'))) a 183 | in (sg:sgs', vs', T.LocalVar (i + length vs'): as', Nothing:names) 184 | 185 | isRewrite :: Prop -> Bool 186 | isRewrite (Forall _ _ c) | (T.Const "_=_" False, rest) <- T.peelApTelescope c = True 187 | isRewrite _ = False 188 | 189 | isIntroduction :: Prop -> Bool 190 | isIntroduction (Forall _ _ c) | (T.Const _ _, rest) <- T.peelApTelescope c = True 191 | isIntroduction _ = False 192 | 193 | introRoot :: Prop -> (MisoString, Int) 194 | introRoot (Forall _ _ c) | (T.Const k _, rest) <- T.peelApTelescope c = (k, length rest) 195 | introRoot _ = error "Not an intro rule!" 196 | 197 | unifierProp :: Prop -> Prop -> UnifyM T.Subst 198 | unifierProp (Forall [] [] p1) (Forall [] [] p2) = unifier p1 p2 199 | unifierProp _ _ = empty 200 | -------------------------------------------------------------------------------- /README.org: -------------------------------------------------------------------------------- 1 | * Holbert 2 | 3 | Holbert is an interactive theorem prover, or proof assistant, based on higher order logic and natural deduction. 4 | Furthermore, Holbert is graphical. It presents proofs and rules using conventional inference rule notation and proof trees. It is designed to be used by students, without 5 | any expertise on using a theorem prover. It does not feature proof scripts (in the traditional sense), tactics, or other such complications. 6 | 7 | You can try Holbert out by trying the live demo [[http://liamoc.net/holbert][here]] (this version may not be the latest one available from GitHub). This Holbert instance explains 8 | more about the rationale behind its design and my intended goals with it. 9 | 10 | Like Isabelle, Holbert is just a pure meta-logic. It does not define any connectives (like conjunction or disjunction) itself, although all can be defined within 11 | the system. For binding structures and quantifiers, higher order abstract syntax can be used. 12 | 13 | Unlike conventional theorem provers, Holbert's term language is just the untyped lambda calculus. While this technically makes the logic 14 | unsound, it is much simpler to use as a pedagogical tool. 15 | 16 | Holbert is intended as a tool for education, and not as an industrial-strength proof assistant where theorems must be trusted. So, just avoid writing fixed point combinators 17 | and you should be fine. 18 | 19 | ** Building, Installing 20 | 21 | Holbert is written in GHC Haskell, intended to be compiled with ~ghcjs~. It uses the Miso framework and the ~optics-core~ library. Acquiring GHCJS can be difficult, 22 | but I was able to follow the instructions on the [[https://github.com/dmjio/miso/blob/master/README.md][Miso readme]] to install it using ~nix~, and then I just used ~cabal~ from then on once 23 | I had the ~ghcjs~ binaries. 24 | 25 | Once it is set up, make sure that the ~OUTPUT~ variable in the ~Makefile~ points to wherever ~cabal~ builds the ~jsexe~ directory for the compiled app. To find out what this is, you can type: 26 | #+BEGIN_EXAMPLE 27 | cabal configure --ghcjs 28 | cabal build 29 | #+END_EXAMPLE 30 | The correct directory to set ~OUTPUT~ to will be listed as the last line in the build log (~Linking ...~), but you can also find it by typing: 31 | #+BEGIN_EXAMPLE 32 | find . | grep jsexe | head -1 33 | #+END_EXAMPLE 34 | 35 | Once the ~OUTPUT~ directory is set, you can build Holbert properly (including all resources) by typing: 36 | #+BEGIN_EXAMPLE 37 | make 38 | #+END_EXAMPLE 39 | And if you have ~python3~ there is a shortcut to start a server with the app with 40 | #+BEGIN_EXAMPLE 41 | make server 42 | #+END_EXAMPLE 43 | 44 | ** Licenses 45 | 46 | Holbert is released under the BSD3 license. It includes the following free projects: 47 | - Computer Modern font families, released under the SIL Open Font License. 48 | - The Neo Euler font, also released under the SIL Open Font License. 49 | - The Typicons icon font, also released under the SIL Open Font License. 50 | 51 | Some code for the unification engine were taken from Tobias Nipkow's paper on the topic, as well as from Daniel Gratzer's higher order unification implementation in Haskell. 52 | 53 | The following MIT licensed JS libraries are used: 54 | 55 | - [[https://github.com/nathancahill/split][Split.js]] by Nathan Cahill 56 | - [[https://github.com/eligrey/FileSaver.js][FileSaver.js]] by Eli Grey 57 | 58 | ** Future work 59 | 60 | - Support for deferred proof steps to lemmas. 61 | - "Books", multiple interlinked documents. 62 | - And much much more! 63 | -------------------------------------------------------------------------------- /ROADMAP: -------------------------------------------------------------------------------- 1 | - Multi-file documents 2 | - Imports 3 | - Persistence to local storage 4 | - Submission to server? 5 | - Lockable regions 6 | - Elimination rules and induction 7 | - Defining inductive sets via grammar 8 | - Equality and Definitions (Rayhana) 9 | - Definitions that are stricter than axioms. 10 | - Inductive definitions 11 | - Transitive calculational proofs IN PROGRESS 12 | - Rewriting in assumptions 13 | - Rewriting to use transitivity when rewriting on an equality proof. 14 | - Built-ins 15 | - Strings 16 | - Naturals 17 | - Hidden premises 18 | - e.g. a variable called "xs" in a rule implicity introduces a premise "xs List" but this is not usually displayed prominently and proofs attempt to solve it automatically. 19 | -------------------------------------------------------------------------------- /StringRep.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings, RecursiveDo, StandaloneDeriving, DeriveAnyClass, DeriveGeneric #-} 2 | module StringRep (prettyPrint, parse, SyntaxTable (..), EPM.Associativity(..)) where 3 | 4 | import Data.Char 5 | import Control.Arrow(first) 6 | import Control.Monad(ap, when) 7 | import Data.List 8 | import Data.Function (on) 9 | import Data.Ord(comparing) 10 | import Prelude hiding (lex) 11 | import Data.Maybe 12 | import Control.Monad.Except 13 | import Control.Applicative hiding (Const) 14 | import Control.Monad.State 15 | import qualified Miso.String as MS 16 | import qualified Data.Text.Lazy.Builder as B 17 | import qualified Data.Text.Lazy as L 18 | import Terms 19 | import qualified Text.Earley as EP 20 | import qualified Text.Earley.Mixfix as EPM 21 | import Data.Aeson(ToJSON, FromJSON) 22 | import GHC.Generics(Generic) 23 | data Token = LParen | RParen | Word MS.MisoString | Dot | Binder MS.MisoString deriving (Show, Eq) 24 | deriving instance Generic EPM.Associativity 25 | deriving instance FromJSON EPM.Associativity 26 | deriving instance ToJSON EPM.Associativity 27 | holey :: MS.MisoString -> EPM.Holey MS.MisoString 28 | holey str = case MS.uncons str of 29 | Nothing -> [] 30 | Just ('_',xs) -> Nothing : holey xs 31 | Just _ -> Just (MS.toMisoString i) : holey rest 32 | where (i, rest) = MS.span (/= '_') str 33 | 34 | concatMixfix :: EPM.Holey Token -> MS.MisoString 35 | concatMixfix xs = MS.ms $ B.toLazyText $ go xs 36 | where 37 | go [] = B.fromText "" 38 | go (Nothing:xs) = B.fromText "_" <> go xs 39 | go ((Just (Word x)):xs) = (B.fromText $ MS.fromMisoString x) <> go xs 40 | 41 | type SyntaxTable = [(Int, MS.MisoString,EPM.Associativity)] 42 | 43 | 44 | generateTable :: SyntaxTable -> [[(EPM.Holey MS.MisoString, EPM.Associativity)]] 45 | generateTable tbl = (map . map) (\(_,str, a) -> (holey str, a)) $ groupBy ((==) `on` precedence) $ sortBy (comparing precedence) tbl 46 | where precedence (a,b,c) = a 47 | 48 | grammar :: SyntaxTable -> EP.Grammar r (EP.Prod r Token Token Term) 49 | grammar tbl = mdo 50 | ident <- EP.rule $ getWord <$> EP.satisfy isLegalWord 51 | atom <- EP.rule $ smartConst <$> ident 52 | <|> EP.namedToken LParen *> program <* EP.namedToken RParen 53 | normalApp <- EP.rule $ atom 54 | <|> Ap <$> normalApp <*> atom 55 | mixfixApp <- EPM.mixfixExpression table normalApp mixfixCon 56 | program <- EP.rule $ mixfixApp 57 | <|> Lam . maskCon <$> EP.satisfy isLegalBinder <*> program 58 | return program 59 | where 60 | maskCon (Binder b) = M b 61 | smartConst c = case MS.uncons c of 62 | Just ('@',xs) -> Const xs True 63 | _ -> Const c False 64 | mixfixCon op ts = applyApTelescope (smartConst $ concatMixfix op) ts 65 | getWord (Word w) = w 66 | tbl' = generateTable tbl 67 | table = map (map $ first $ map $ fmap (EP.namedToken . Word)) $ tbl' 68 | illegalIdents = [s | xs <- tbl' , (ys, _) <- xs , Just s <- ys] 69 | isLegalBinder (Binder b) = not $ elem b illegalIdents 70 | isLegalBinder _ = False 71 | isLegalWord (Word w) = not $ elem w illegalIdents 72 | isLegalWord _ = False 73 | 74 | postProc :: [Name] -> Term -> Term 75 | postProc ctx (Lam (M b) t) = Lam (M b) $ postProc (b:ctx) t 76 | postProc ctx (Ap t1 t2) = Ap (postProc ctx t1) (postProc ctx t2) 77 | postProc ctx (Const x False) | Just v <- elemIndex x ctx = LocalVar v 78 | | otherwise = Const x False 79 | postProc ctx (Const x True) = Const x True 80 | 81 | type Error = MS.MisoString 82 | 83 | printHoley :: MS.MisoString -> [B.Builder] -> B.Builder 84 | printHoley origin operends = go origin origin operends 85 | where 86 | go origin op [] = B.fromText $ MS.fromMisoString op 87 | go origin op (x:xs) = case MS.uncons op of 88 | Just ('_', ops) | origin == op -> x <> " " <> go origin ops xs 89 | | ops == "" -> " " <> x <> go origin ops xs 90 | | otherwise -> " " <> x <> " " <> go origin ops xs 91 | Just (o, ops) -> B.singleton o <> go origin ops (x:xs) 92 | 93 | prettyPrint :: SyntaxTable -> [Name] -> Term -> MS.MisoString 94 | prettyPrint tbl ctx t = MS.ms $ B.toLazyText $ go ctx t 95 | where 96 | go :: [Name] -> Term -> B.Builder 97 | go ctx (Lam (M x) t) = B.fromText (MS.fromMisoString x) <> ". " <> go (x:ctx) t 98 | go ctx e = go' ctx e 99 | go' ctx (Ap a1 a2) 100 | | (x, ts) <- peelApTelescope (Ap a1 a2) = case x of 101 | Const op b 102 | | isMixfix op b, MS.count "_" op == length ts -> printHoley (if b then "@" <> op else op) $ (map $ go'' ctx) ts 103 | _ -> go' ctx a1 <> " " <> go'' ctx a2 104 | where 105 | isMixfix op b = elem (if b then "@"<>op else op) [ys | (_,ys, _) <- tbl] 106 | 107 | go' ctx (Lam n t) = "(" <> go ctx (Lam n t) <> ")" 108 | go' ctx e = go'' ctx e 109 | go'' ctx (LocalVar v) = B.fromText (MS.fromMisoString (ctx !! v)) 110 | go'' ctx (Const id c) = (if c then "@" else mempty) <> (B.fromText $ MS.fromMisoString $ id) 111 | go'' ctx (MetaVar id) = "?" <> B.fromText (MS.fromMisoString $ MS.pack (show id)) 112 | go'' ctx e = "(" <> go ctx e <> ")" 113 | 114 | lexer :: MS.MisoString -> [Token] 115 | lexer str | (x,y) <- MS.span isSpace str 116 | , not (MS.null x) = lexer y 117 | lexer str = case MS.uncons str of 118 | Nothing -> [] 119 | Just ('(',rest) -> LParen:lexer rest 120 | Just (')',rest) -> RParen:lexer rest 121 | Just ('.',rest) -> Dot:lexer rest 122 | _ | (word,rest) <- MS.span (\c -> not (isSpace c) && c `notElem` ("()." :: String)) str 123 | -> Word word : lexer rest 124 | 125 | preprocess (Word s : Dot : rest) = Binder s : preprocess rest 126 | preprocess (x:xs) = x : preprocess xs 127 | preprocess [] = [] 128 | 129 | unlex LParen = "(" 130 | unlex RParen = ")" 131 | unlex Dot = "." 132 | unlex (Binder s) = s <> "." 133 | unlex (Word s) = s 134 | 135 | type Parser a = ExceptT MS.MisoString (State [Token]) a 136 | 137 | fromMixfix :: SyntaxTable -> [Name] -> MS.MisoString -> Either Error Term 138 | fromMixfix tbl ctx s = case EP.fullParses (EP.parser $ grammar tbl) $ preprocess . lexer $ s of 139 | ([], rep) -> Left $ "Parse error: unexpected character at position " <> MS.toMisoString (EP.position rep) 140 | ([x], rep) -> Right $ postProc ctx x 141 | ((x:xs), rep) -> Left $ "Parse error: ambiguous parsing result: " <> MS.concat (map ((prettyPrint tbl ctx). (postProc ctx)) (x:xs)) 142 | 143 | parse :: SyntaxTable -> [Name] -> MS.MisoString -> Either Error Term 144 | parse = fromMixfix 145 | -------------------------------------------------------------------------------- /SyntaxDecl.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE TypeFamilies, DeriveAnyClass, DeriveGeneric, OverloadedStrings #-} 2 | module SyntaxDecl where 3 | import Controller 4 | import Miso.String as MS hiding (splitAt, length) 5 | import GHC.Generics(Generic) 6 | import Data.Aeson (ToJSON,FromJSON) 7 | import StringRep 8 | import Data.Char 9 | 10 | data SyntaxDecl = SyntaxDecl [(Int, MisoString, Associativity)] 11 | deriving (Show, Eq, Generic, ToJSON, FromJSON) 12 | 13 | 14 | instance Control SyntaxDecl where 15 | data Focus SyntaxDecl = SelectName Int | SelectPrec Int 16 | deriving (Show, Eq) 17 | data Action SyntaxDecl = EditName Int | EditPrec Int | SetAssoc Associativity Int | RemoveDecl Int | AddDecl 18 | deriving (Show, Eq) 19 | 20 | editable _ (SelectName i) (SyntaxDecl ls) | (_,s,_) <- ls !! i = Just s 21 | editable _ (SelectPrec i) (SyntaxDecl ls) | (p, _, _) <- ls !! i = Just (MS.pack $ show p) 22 | editable _ _ _ = Nothing 23 | 24 | leaveFocus _ = pure 25 | 26 | handle (SetAssoc a i) (SyntaxDecl ls) = do 27 | let (lefts,(p,s,_):rights) = splitAt i ls 28 | pure (SyntaxDecl (lefts ++ (p, s, a):rights)) 29 | handle (EditPrec i) (SyntaxDecl ls) = do 30 | let (lefts,(_,s,a):rights) = splitAt i ls 31 | new <- textInput 32 | let p = read $ MS.unpack new 33 | pure (SyntaxDecl (lefts ++ (p,s,a):rights)) 34 | handle (EditName i) (SyntaxDecl ls) = do 35 | let (lefts,(p,s,a):rights) = splitAt i ls 36 | new <- textInput 37 | case new of 38 | "" -> errorMessage "Syntax cannot be empty" 39 | _ | MS.any Data.Char.isSpace new -> errorMessage "Syntax cannot contain spaces" 40 | _ | not (MS.any (=='_') new) -> errorMessage "Syntax must contain at least one underscore" 41 | _ -> pure () 42 | -- Check for notation conflicts? 43 | pure (SyntaxDecl (lefts++ (p,new,a):rights)) 44 | handle (RemoveDecl i) (SyntaxDecl ls) = do 45 | let (lefts,_:rights) = splitAt i ls 46 | pure (SyntaxDecl (lefts++rights)) 47 | handle (AddDecl) (SyntaxDecl ls) = do 48 | setFocus (SelectName (length ls)) 49 | pure (SyntaxDecl (ls ++ [(0,"???",NonAssoc)])) 50 | 51 | inserted _ = SelectName 0 52 | 53 | definedSyntax (SyntaxDecl ls) = ls 54 | -------------------------------------------------------------------------------- /Terms.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE FlexibleContexts, DeriveGeneric, DeriveAnyClass, OverloadedStrings #-} 2 | module Terms 3 | ( Term (..), Masked (..), Id, Name 4 | , raise, raise' 5 | , isUsed 6 | , subst 7 | , substMV 8 | , reduce 9 | , peelApTelescope, applyApTelescope 10 | , Subst, applySubst, fromUnifier 11 | , invalidName 12 | , Index 13 | , mentioned 14 | ) where 15 | 16 | import qualified Data.Map as M 17 | import Data.String 18 | import Data.List (foldl') 19 | import Data.Char (isSpace) 20 | import GHC.Generics (Generic) 21 | import Data.Aeson (ToJSON, FromJSON) 22 | import qualified Miso.String as MS 23 | -- Judge equality of terms modulo alpha equivalence. 24 | -- we do this by hiding names from the Eq instance. 25 | type Name = MS.MisoString 26 | type Id = Int 27 | newtype Masked a = M a deriving (Generic, ToJSON, FromJSON) 28 | instance Eq (Masked a) where 29 | _ == _ = True 30 | instance Show a => Show (Masked a) where 31 | show (M a) = show a 32 | instance Ord (Masked a) where 33 | compare _ _ = EQ 34 | instance IsString a => IsString (Masked a) where 35 | fromString = M . fromString 36 | 37 | type Index = Int 38 | data Term = LocalVar Index 39 | | MetaVar Id 40 | | Ap Term Term 41 | | Const Name Bool 42 | | Lam (Masked Name) Term 43 | deriving (Show, Eq, Ord, Generic, ToJSON, FromJSON) 44 | 45 | mentioned :: Term -> [Index] -- generlaise with these idxs 46 | mentioned (LocalVar i) = [i] 47 | mentioned (Ap a b) = mentioned a ++ mentioned b 48 | mentioned (Lam _ t) = map (subtract 1) $ filter (/= 0) $ mentioned t 49 | mentioned _ = [] 50 | 51 | 52 | invalidName "" = Just "Name cannot be empty" 53 | invalidName s | MS.any isSpace s = Just "Name contains spaces" 54 | invalidName s | MS.any (`elem` ("()." :: String)) s = Just "Name contains reserved symbols" 55 | invalidName s = Nothing 56 | 57 | raise :: Int -> Term -> Term 58 | raise = raise' 0 59 | 60 | raise' :: Int -> Int -> Term -> Term 61 | raise' lower i t = case t of 62 | LocalVar j -> if j >= lower then LocalVar (i + j) else LocalVar j 63 | MetaVar i -> MetaVar i 64 | Const s con -> Const s con 65 | Ap l r -> raise' lower i l `Ap` raise' lower i r 66 | Lam n body -> Lam n (raise' (lower + 1) i body) 67 | 68 | isUsed :: Int -> Term -> Bool 69 | isUsed i (LocalVar j) = i == j 70 | isUsed i (Lam _ t) = isUsed (i+1) t 71 | isUsed i (Ap t u) = isUsed i t || isUsed i u 72 | isUsed i _ = False 73 | 74 | 75 | subst :: Term -> Int -> Term -> Term -- use this! 76 | subst new i t = case t of 77 | LocalVar j -> case compare j i of 78 | LT -> LocalVar j 79 | EQ -> new 80 | GT -> LocalVar (j - 1) 81 | MetaVar i -> MetaVar i 82 | Ap l r -> subst new i l `Ap` subst new i r 83 | Const s c -> Const s c 84 | Lam n body -> Lam n (subst (raise 1 new) (i + 1) body) 85 | 86 | substMV :: Term -> Id -> Term -> Term 87 | substMV new i t = case t of 88 | LocalVar i -> LocalVar i 89 | MetaVar j -> if i == j then new else MetaVar j 90 | Ap l r -> substMV new i l `Ap` substMV new i r 91 | Const s c -> Const s c 92 | -- This raising should not be strictly necessary as metavariables should not be subbed for open terms 93 | Lam n body -> Lam n (substMV (raise 1 new) i body) 94 | 95 | reduce :: Term -> Term 96 | reduce t = case t of 97 | LocalVar j -> LocalVar j 98 | MetaVar i -> MetaVar i 99 | Const i c -> Const i c 100 | Ap l r -> case reduce l of 101 | Lam n body -> reduce (subst r 0 body) 102 | l' -> Ap l' (reduce r) 103 | Lam n body -> Lam n (reduce body) 104 | 105 | peelApTelescope :: Term -> (Term, [Term]) 106 | peelApTelescope t = go t [] 107 | where go (Ap f r) rest = go f (r : rest) 108 | go t rest = (t, rest) 109 | 110 | applyApTelescope :: Term -> [Term] -> Term 111 | applyApTelescope = foldl' Ap 112 | 113 | newtype Subst = S (M.Map Id Term) 114 | instance Semigroup Subst where 115 | S s1 <> S s2 | not (M.null (M.intersection s1 s2)) = error "Impossible" 116 | | otherwise = S $ M.union (applySubst (S s1) <$> s2) (applySubst (S s2) <$> s1) 117 | instance Monoid Subst where 118 | mempty = S (M.empty) 119 | 120 | applySubst :: Subst -> Term -> Term 121 | applySubst (S s) t = reduce $ M.foldrWithKey (\mv sol t -> substMV sol mv t) t s 122 | 123 | fromUnifier :: [(Id,Term)] -> Subst 124 | fromUnifier [] = mempty 125 | fromUnifier ((x,v):ts) = let S s = fromUnifier ts 126 | in S $ M.insert x v (substMV v x <$> s) 127 | 128 | -- free vars func 129 | -------------------------------------------------------------------------------- /Unification.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE FlexibleContexts, OverloadedStrings #-} 2 | module Unification (unifier, fresh, UnifyM, runUnifyM, UnifyError) where 3 | import qualified Miso.String as MS 4 | import Control.Monad 5 | import Control.Monad.State 6 | import Control.Monad.Trans 7 | import Control.Monad.Except 8 | import qualified Data.Map.Strict as M 9 | import Data.Maybe 10 | import Data.Foldable 11 | import qualified Data.Set as S 12 | 13 | import Terms 14 | 15 | -- almost all of this is a direct port of Tobias Nipkow's pattern unification implementation 16 | -- in standard ML. 17 | type UnifyError = MS.MisoString 18 | 19 | gen = do x <- get; put (x + 1); pure x 20 | 21 | lams (x:xs) t = Lam (M "x") (lams xs t) 22 | lams [] t = t 23 | 24 | hnf xs f ss = lams xs (applyApTelescope f ss) 25 | 26 | occ f sS (MetaVar g) = (f == g) || (case lookup g sS of 27 | Just s -> occ f sS s 28 | Nothing -> False) 29 | occ f sS (Ap s t) = occ f sS s || occ f sS t 30 | occ f sS (Lam _ t) = occ f sS t 31 | occ f sS _ = False 32 | 33 | 34 | mapbnd f = let mpb d (LocalVar i) = LocalVar (if i Bool) -> [a] -> [Term] 50 | pos p (x:xs) = if p x then LocalVar(length xs) : pos p xs else pos p xs 51 | pos p [] = [] 52 | 53 | posM p (x:xs) = do c <- p x; if c then (LocalVar(length xs):) <$> posM p xs else posM p xs 54 | posM p [] = pure [] 55 | idx (b:bs) b' = if b==b' then LocalVar(length bs) else idx bs b' 56 | idx [] _ = LocalVar(-10000) 57 | 58 | 59 | fresh = MetaVar <$> lift gen 60 | 61 | proj sS s = case peelApTelescope (devar sS s) of 62 | (Lam _ t,_) -> proj sS t 63 | (Const _ _,ss) -> foldlM proj sS ss 64 | (LocalVar i,ss) | i >= 0 -> foldlM proj sS ss 65 | | otherwise -> throwError "Unification Failure i < 0" 66 | (MetaVar f,bs) -> do 67 | var <- fresh 68 | bs' <- posM ( \ t -> case t of (LocalVar i) -> pure (i >= 0) 69 | otherthing -> throwError "Non-pattern equation" ) bs 70 | pure ((f , hnf bs var bs' ):sS) 71 | 72 | 73 | flexflex1 f ym zn sS 74 | | ym == zn = pure $ sS 75 | | otherwise = do 76 | var <- fresh 77 | pure ((f, hnf ym var (pos (uncurry (==)) (zip ym zn))) : sS) 78 | 79 | 80 | subset :: (Eq a) => [a] -> [a] -> Bool 81 | subset as bs = all (`elem` bs) as 82 | 83 | intersection :: (Eq a) => [a] -> [a] -> [a] 84 | intersection xs ys = filter (`elem` ys) xs 85 | 86 | flexflex2 f im g jn sS 87 | | im `subset` jn = pure $ ((g, lam' jn (MetaVar f) im) : sS ) 88 | | jn `subset` im = pure $ ((f, lam' im (MetaVar g) jn) : sS) 89 | | otherwise = do 90 | let kl = im `intersection` jn 91 | h <- fresh 92 | pure ((f, lam' im h kl ) : (g, lam' jn h kl ) : sS) 93 | where 94 | lam' im g jn = hnf im g (map (idx im) jn) 95 | 96 | 97 | flexflex f ym g zn sS 98 | | f == g = flexflex1 f ym zn sS 99 | | otherwise = flexflex2 f ym g zn sS 100 | 101 | flexrigid f im t sS 102 | | occ f sS t = throwError "Unification failure (occurs check)" 103 | | otherwise = let u = mapbnd (\i -> let (LocalVar n) = idx im (LocalVar i) in n) t 104 | in proj((f,lams im u):sS) u 105 | 106 | unif sS (s,t) = case (devar sS s,devar sS t) of 107 | (Lam _ s, Lam _ t) -> unif sS (s,t) 108 | (Lam _ s,t) -> unif sS (s, Ap (incr t) (LocalVar 0)) 109 | (s,Lam _ t) -> unif sS (Ap (incr s) (LocalVar 0), t) 110 | (s,t) -> cases sS (s,t) 111 | 112 | cases sS (s,t) = case (peelApTelescope s,peelApTelescope t) of 113 | ((MetaVar f,ym),(MetaVar g,zn)) -> flexflex f ym g zn sS 114 | ((MetaVar f,ym),_) -> flexrigid f ym t sS 115 | (_,(MetaVar f,ym)) -> flexrigid f ym s sS 116 | ((a,sm),(b,tn)) -> rigidrigid a sm b tn sS 117 | 118 | rigidrigid a ss b ts sS 119 | | a == b, length ss == length ts = foldlM unif sS (zip ss ts) 120 | | otherwise = throwError (MS.toMisoString (concat ["Unification Error (", show a, ", ", show b, ")"])) --"Unification Error (rigid, rigid)" 121 | 122 | type Gen = State Int 123 | 124 | type UnifyM = ExceptT MS.MisoString (State Int) 125 | 126 | 127 | 128 | unifier :: Term -> Term -> UnifyM Subst 129 | unifier t1 t2 = fromUnifier <$> unif [] (t1,t2) 130 | 131 | runUnifyM = runState . runExceptT 132 | -------------------------------------------------------------------------------- /View/Heading.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings #-} 2 | 3 | module View.Heading where 4 | import Miso 5 | import qualified Miso.String as MS 6 | import qualified Heading as H 7 | import View.Term 8 | import View.Utils 9 | 10 | renderHeading i textIn selected (H.Heading l txt) = case selected of 11 | Just _ -> anchor i [editor ("heading h" <> (MS.pack $ show l)) H.Edit textIn] 12 | _ -> button "editable editable-heading" "" (SetFocus H.Select) 13 | [ case l of 14 | 0 -> h1_ [] [anchor i [text txt]] 15 | 1 -> h2_ [] [anchor i [text txt]] 16 | 2 -> h3_ [] [anchor i [text txt]] 17 | 3 -> h4_ [] [anchor i [text txt]] 18 | _ -> h5_ [] [anchor i [text txt]] 19 | ] -------------------------------------------------------------------------------- /View/Item.hs: -------------------------------------------------------------------------------- 1 | module View.Item where 2 | import qualified Editor as E 3 | import qualified Item as I 4 | import View.Utils 5 | import View.Heading 6 | import View.Rule 7 | import View.Paragraph 8 | import View.SyntaxDecl 9 | 10 | toGlobalAction :: Int -> LocalAction (I.Focus I.Item) (I.Action I.Item) -> E.EditorAction 11 | toGlobalAction _ (UpdateInput s) = E.UpdateInput s 12 | toGlobalAction _ Reset = E.Reset 13 | toGlobalAction _ Noop = E.Noop 14 | toGlobalAction i (Act a) = E.ItemAction (Just i) a 15 | toGlobalAction i (SetFocus f) = E.SetFocus (E.ItemFocus i f) 16 | 17 | toLocalFocus :: Int -> E.EditorFocus -> Maybe (I.Focus I.Item) 18 | toLocalFocus i (E.ItemFocus i' f) | i == i' = Just f 19 | toLocalFocus _ _ = Nothing 20 | 21 | renderItem opts index tbl textIn item focus = case item of 22 | I.Paragraph para -> fmap (toGlobalAction index . mapLocalAction I.ParagraphFocus I.ParagraphAct) 23 | $ renderParagraph tbl textIn (fmap (\(I.ParagraphFocus p) -> p) $ toLocalFocus index focus) para 24 | I.Heading head -> fmap (toGlobalAction index . mapLocalAction I.HeadingFocus I.HeadingAct) 25 | $ renderHeading index textIn (fmap (\(I.HeadingFocus p) -> p) $ toLocalFocus index focus) head 26 | I.SyntaxDecl sd -> fmap (toGlobalAction index . mapLocalAction I.SyntaxDeclFocus I.SyntaxDeclAct) 27 | $ renderSyntaxDecl index textIn (fmap (\(I.SyntaxDeclFocus p) -> p) $ toLocalFocus index focus) sd 28 | I.Rule rule -> fmap (toGlobalAction index . mapLocalAction I.RuleFocus I.RuleAct) 29 | $ renderRule index opts tbl textIn (fmap (\(I.RuleFocus p) -> p) $ toLocalFocus index focus) rule 30 | -------------------------------------------------------------------------------- /View/Paragraph.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings #-} 2 | module View.Paragraph where 3 | import Miso 4 | import DisplayOptions 5 | import StringRep as SR 6 | import qualified Item as I 7 | import qualified Miso.String as MS 8 | import qualified Paragraph as P 9 | import qualified Prop as P 10 | import qualified Terms as T 11 | import View.Term 12 | import View.Utils 13 | import View.Prop 14 | 15 | renderText tbl txt = normalText txt 16 | where 17 | normalText txt = case MS.span (`notElem` ("~/$*^@" :: String)) txt of 18 | (first, crest) | MS.null crest -> [text first] 19 | (first, crest) | Just (c, rest) <- MS.uncons crest -> text first : case MS.span (/= c) rest of 20 | (rfirst, crest') | MS.null rfirst, Just (_, rest') <- MS.uncons crest' -> text (MS.pack [c]) : normalText rest' 21 | (rfirst, crest') | MS.null crest' -> tagsFor c rfirst 22 | (rfirst, crest') | Just (_, rest') <- MS.uncons crest' -> tagsFor c rfirst ++ normalText rest' 23 | 24 | tagsFor '^' txt | (ls, rs) <- MS.span (/= ':') txt, not (MS.null rs) = [sup_ [class_ "footnote"] [text ls, span_ [class_ "footnote-box"] (renderText tbl (MS.tail rs))] ] 25 | | otherwise = [text txt] 26 | tagsFor '~' txt = [code_ [] [text txt]] 27 | tagsFor '@' "goalTag" = [span_ [class_ "typcn typcn-location-outline inline-icon-example"] []] 28 | tagsFor '@' "entailment" = [turnstile] 29 | tagsFor '@' txt | (ls, rs) <- MS.span (/= '|') txt, not (MS.null rs) = 30 | if ls == "image" then [img_ [src_ (MS.tail rs)]] else [a_ [href_ (MS.tail rs)] [text ls]] 31 | | otherwise = [a_ [href_ txt] [text txt]] 32 | tagsFor '/' txt = [i_ [] [text txt]] 33 | tagsFor '*' txt = [b_ [] [text txt]] 34 | tagsFor '$' txt = let spans = MS.span (/= ':') txt 35 | in case spans of 36 | (".thm", crest) | Just (_, rest) <- MS.uncons crest -> [inline "rule-rulename-defined" (name rest)] 37 | (".rule", crest) | Just (_, crest2) <- MS.uncons crest 38 | , Just rule <- parseRule [] [] crest2 39 | -> [inline "inline-math" [fmap (const Noop) $ renderProp [] (RDO (TDO True True) True Turnstile) rule]] 40 | _ -> let (ctx, txt') = case spans of 41 | (_, crest) | MS.null crest -> ([], txt) 42 | (ctx, crest) | Just (_, rest) <- MS.uncons crest -> (MS.words ctx, rest) 43 | in case SR.parse tbl ctx txt' of 44 | Left _ -> ["$", text txt, "$"] 45 | Right t -> [inline "inline-math" [renderTermCtx ctx (TDO True True) t]] 46 | deparen "" = "" 47 | deparen str | MS.head str == '(' && MS.last str == ')' = deparen (MS.tail (MS.init str)) 48 | | MS.head str == ' ' = deparen (MS.tail str) 49 | | MS.last str == ' ' = deparen (MS.init str) 50 | | otherwise = str 51 | parseRule ctx ctx' str | (name, rest) <- MS.span (/= '.') str 52 | , Nothing <- T.invalidName name 53 | , Just ('.', rest') <- MS.uncons rest 54 | = parseRule ctx (name:ctx') rest' 55 | parseRule ctx ctx' str | Just (P.Forall [] lcls conc) <- parseRule' (ctx' ++ ctx) str 56 | = Just (P.Forall (reverse ctx') lcls conc) 57 | parseRule ctx ctx' str | Just (P.Forall [] [] conc) <- parseRule'' (ctx' ++ ctx) str 58 | = Just (P.Forall (reverse ctx') [] conc) 59 | | otherwise = Nothing 60 | parseRule' ctx str | (body, rest) <- spanModuloParens (`notElem` [',','|']) str 61 | , Just (',', rest') <- MS.uncons rest 62 | , Just l <- parseRule ctx [] (deparen body) 63 | , Just (P.Forall [] lcls conc) <- parseRule' ctx rest' 64 | = Just (P.Forall [] (l:lcls) conc ) 65 | parseRule' ctx str | (body, rest) <- spanModuloParens (`notElem` [',','|']) str 66 | , Just ('|', rest') <- MS.uncons rest 67 | , Just ('-', rest'') <- MS.uncons rest' 68 | , Just l <- parseRule ctx [] body 69 | , Right conc <- SR.parse tbl ctx rest'' 70 | = Just (P.Forall [] [l] conc) 71 | | otherwise = Nothing 72 | parseRule'' ctx str | Right conc <- SR.parse tbl ctx str 73 | = Just (P.Forall [] [] conc) 74 | | otherwise = Nothing 75 | renderParagraph tbl textIn selected (P.Paragraph txt) = 76 | block "" $ case selected of 77 | Just P.Select -> 78 | [ block "item-options-bottom" 79 | [ iconButton "blue" "Confirm edits" "tick-outline" (Act P.Edit) 80 | , iconButton "grey" "Cancel edits" "times-outline" Reset 81 | ] 82 | , expandingTextarea "ta" "paragraph" UpdateInput textIn 83 | ] 84 | Nothing -> 85 | [ block "item-options-bottom" 86 | [ iconButton "blue" "Edit paragraph" "edit" (SetFocus P.Select)] 87 | , block "paragraph" (renderText tbl txt) 88 | ] 89 | -------------------------------------------------------------------------------- /View/Prop.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings #-} 2 | module View.Prop where 3 | import Miso 4 | import qualified Miso.String as MS 5 | import DisplayOptions 6 | import qualified Rule as R 7 | import Terms 8 | import Prop 9 | import View.Utils 10 | import View.Term 11 | 12 | data RuleDisplayOptions = RDO { termDisplayOptions :: TermDisplayOptions, showInitialMetas :: Bool, ruleStyle :: RuleStyle } 13 | 14 | data EditableMode = NotEditable 15 | | Editable (Maybe R.RuleFocus) Bool MS.MisoString --boolean "is this deletable?" 16 | | InProofTree (Maybe (R.RuleFocus), MS.MisoString) 17 | 18 | renderProp = renderPropName Nothing 19 | renderPropName = renderPropNameE NotEditable 20 | renderPropNameE = renderPropNameLabelledE Nothing Nothing 21 | 22 | renderPropNameLabelledE labels ptpath editable n ctx opts prp = renderP labels (showInitialMetas opts) n (ruleStyle opts) ctx [] prp 23 | where 24 | metabinders pth vs = wrap $ 25 | zipWith (metabinder' pth) [0 ..] vs ++ 26 | case editable of 27 | Editable selected deletable n -> case selected of 28 | Just (R.NewRuleBinderFocus pth') | pth == pth' -> [editor "expanding" (R.AddRuleBinder pth) n] 29 | Just (R.RuleTermFocus pth') | pth == pth' -> 30 | [ iconButton "blue button-icon-addbinder" "Add Variable" "plus" (SetFocus $ R.NewRuleBinderFocus pth) 31 | , inline "metabinder" ["."] 32 | ] 33 | _ -> [] 34 | _ -> [] 35 | where 36 | wrap [] = multi [] 37 | wrap cs = inline "rule-binders" cs 38 | 39 | currentGS = case editable of 40 | InProofTree (Just (R.ProofFocus _ g), _) -> g 41 | _ -> Nothing 42 | 43 | metabinder' pth i n = case editable of 44 | Editable selected _ n' -> 45 | editableMath n' (metabinder n) (R.RuleBinderFocus pth i) (R.RenameRuleBinder pth i) 46 | [iconButton "red" "Remove Variable" "trash" (Act $ R.DeleteRuleBinder pth i)] 47 | selected 48 | InProofTree (selected, n') | pth == [], Just pth' <- ptpath -> 49 | editableMath n' (metabinder n) (flip R.ProofFocus currentGS $ R.ProofBinderFocus pth' i) (R.RenameProofBinder pth' i) 50 | [] selected 51 | _ -> metabinder n 52 | 53 | renderTerm' ctx pth trm = case editable of 54 | Editable selected _ n -> 55 | editableMath n (renderTermCtx ctx (termDisplayOptions opts) trm) (R.RuleTermFocus pth) (R.UpdateTerm pth) 56 | (if null pth then [] else [iconButton "red" "Delete Premise" "trash" (Act $ R.DeletePremise pth)]) 57 | selected 58 | InProofTree (selected, n) -> 59 | renderTermCtxEditable (Just (n, flip R.ProofFocus currentGS . R.MetavariableFocus, R.InstantiateMetavariable, selected)) ctx (termDisplayOptions opts) trm 60 | _ -> renderTermCtx ctx (termDisplayOptions opts) trm 61 | 62 | renderRR' rr@(Defn nm) = case editable of 63 | Editable selected deletable n -> multi $ editableMath n (renderRR rr) R.NameFocus R.Rename [] selected : if deletable then [iconButton "red" "Delete axiom" "trash" (Act $ R.DeleteRI)] else [] 64 | _ -> renderRR rr 65 | renderRR' rr = renderRR rr 66 | 67 | renderRR (Defn d) = definedrule d 68 | renderRR (Local i) = localrule i 69 | renderRR (Cases n i) = casesrule n i 70 | renderRR (Induction n i) = inductrule n i 71 | renderRR Refl = builtinrule "refl" 72 | 73 | isSelectedOrBinders pth = case editable of 74 | Editable selected _ n -> case selected of 75 | Just (R.RuleTermFocus pth') | pth == pth' -> True 76 | Just (R.RuleBinderFocus pth' _) | pth == pth' -> True 77 | Just (R.NewRuleBinderFocus pth') | pth == pth' -> True 78 | _ -> False 79 | _ -> False 80 | 81 | isSelected pth = case editable of 82 | Editable (Just (R.RuleTermFocus pth')) _ _ -> pth == pth' 83 | otherwise -> False 84 | 85 | renderP labels showMetas title style ctx pth (Forall sks lcls g) = 86 | let (renderer, nextStyle) = case style of 87 | Bar -> (inferrule, Dots) 88 | BarTurnstile -> (inferrule, Turnstile) 89 | Turnstile -> (entailment (isSelected pth), Turnstile) 90 | Dots -> (hypothetical (isSelected pth), Turnstile) 91 | ctx' = reverse sks ++ ctx 92 | renderNext pth prp | style /= Turnstile = renderP Nothing True (labels >>= lookupMaybe (head pth)) nextStyle ctx' pth prp 93 | renderNext pth prp@(Forall [] [] g) | not (isSelectedOrBinders pth) = renderP Nothing True (labels >>= lookupMaybe (head pth)) nextStyle ctx' pth prp 94 | renderNext pth prp = multi (parenthesise [renderP Nothing True (labels >>= lookupMaybe (head pth)) nextStyle ctx' pth prp]) 95 | lookupMaybe n [] = Nothing 96 | lookupMaybe 0 (x:xs) = Just x 97 | lookupMaybe n (x:xs) = lookupMaybe (n-1) xs 98 | binders = if showMetas then [metabinders pth sks] else [] 99 | premises = zipWith renderNext (map (: pth) [0 ..]) lcls 100 | spacer = 101 | if isSelected pth 102 | then iconButton "blue button-icon-addpremise" "Add Premise" "plus-outline" (Act $ R.AddPremise pth) 103 | else "" 104 | ruleTitle = fmap renderRR' title 105 | conclusion = [renderTerm' ctx' pth g] 106 | in renderer binders premises spacer ruleTitle conclusion 107 | 108 | -------------------------------------------------------------------------------- /View/Rule.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings, TupleSections #-} 2 | module View.Rule where 3 | import Miso 4 | import qualified Miso.String as MS 5 | import Optics.Core 6 | import Data.Maybe (isNothing) 7 | import Data.String 8 | import View.Utils 9 | import View.Prop 10 | import View.ProofTree 11 | import DisplayOptions 12 | import qualified Item as I 13 | import qualified Rule as R 14 | import qualified ProofTree as PT 15 | import qualified Prop as P 16 | import qualified Controller as C 17 | import qualified Editor as E 18 | 19 | renderRule i opts tbl textIn selected rules@(R.R ruleType ris rest) = div_ [class_ classname] 20 | $ case ruleType of 21 | R.Axiom -> axiomHeading i (case ris of [_] -> ""; _ -> "s") 22 | : zipWith (\n (R.RI ruleName prop mpt) -> fmap (wrapping n) 23 | $ block "rule axiom" [renderPropNameE (Editable (selected >>= unwrapping n) True textIn) (Just (P.Defn ruleName)) [] ruleDOs prop] ) 24 | [0..] ris 25 | ++ [block "rule axiom addition" $ pure $ if selected == Just (R.AddingRule) then editor "newrule" R.AddRule textIn else iconButton "blue" "Insert new rule" "plus-outline" (SetFocus $ R.AddingRule)] 26 | R.Theorem -> theoremHeading i 27 | : zipWith (\n (R.RI name prop mpt) -> 28 | fmap (wrapping n) $ multi $ case mpt of 29 | Just ps -> block "rule" [renderPropNameE (Editable (selected >>= unwrapping n) False textIn) (Just (P.Defn name)) [] ruleDOs prop] 30 | : block "item-rule-proofbox" [renderProofTree opts (ps ^. R.proofTree) tbl (selected >>= unwrapping n) textIn] 31 | : [] 32 | Nothing -> [] 33 | ) [0..] ris 34 | R.Inductive -> inductiveHeading i 35 | : zipWith (\n (R.RI ruleName prop mpt) -> fmap (wrapping n) 36 | $ block ("rule " <> classToUse <> if P.isIntroduction prop then "" else " not-intro-error") [renderPropNameE (Editable (selected >>= unwrapping n) True textIn) (Just (P.Defn ruleName)) [] ruleDOs prop] ) 37 | [0..] ris 38 | ++ [block ("rule addition " <> classToUse) $ pure $ if selected == Just (R.AddingRule) then editor "newrule" R.AddRule textIn else iconButton "blue" "Insert new rule" "plus-outline" (SetFocus $ R.AddingRule)] 39 | ++ [collapsableblock (MS.pack $ show i) ["Derived Rules"] $ map (\(name,p) -> block ("rule " <> classToUse) [fmap (wrapping undefined) $ renderPropName (Just name) [] ruleDOs p]) rest] 40 | 41 | where 42 | classname = case ruleType of R.Axiom -> "item-rule-axiom-set"; R.Inductive -> "item-rule-axiom-set"; _ -> "item-rule-theorem-box" 43 | ruleDOs = RDO { termDisplayOptions = tDOs opts, showInitialMetas = showMetaBinders opts, ruleStyle = compactRules opts } 44 | wrapping :: Int -> LocalAction R.RuleFocus R.RuleAction -> LocalAction (R.Focus R.Rule) (R.Action R.Rule) 45 | wrapping i = mapLocalAction (R.RF i) (R.RA i) 46 | unwrapping :: Int -> R.Focus R.Rule -> Maybe R.RuleFocus 47 | unwrapping n (R.RF i rf) = if n == i then Just rf else Nothing 48 | unwrapping n R.AddingRule = Nothing 49 | classToUse = case compactRules opts of Turnstile -> "axiom-block"; _ -> "axiom" 50 | 51 | -------------------------------------------------------------------------------- /View/SyntaxDecl.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings #-} 2 | module View.SyntaxDecl where 3 | import Miso 4 | import qualified Miso.String as MS 5 | import qualified SyntaxDecl as S 6 | import View.Term 7 | import View.Utils 8 | import StringRep (Associativity(..)) 9 | 10 | renderSyntaxDecl i textIn selected (S.SyntaxDecl ls) = 11 | div_ [] (syntaxDeclHeading i: zipWith (\j itm -> renderSyntaxDecl' i j textIn selected itm alone) [0..] ls ++ 12 | [ iconButton "blue" "Insert new notation" "plus-outline" (Act $ S.AddDecl) ]) 13 | where 14 | alone = length ls == 1 15 | 16 | renderSyntaxDecl' i j textIn selected (l, n, assoc) alone = 17 | div_ [class_ $ if alone then "item-syntax item-syntax-single" else "item-syntax"] [ 18 | case selected of 19 | Just (S.SelectName j') | j == j' -> editor "expanding" (S.EditName j) textIn 20 | _ -> button "editable" "" (SetFocus (S.SelectName j)) (name n) 21 | , select_ [class_ "editable", onChange (Act . flip S.SetAssoc j . toAssoc) ] 22 | [ option_ [value_ "none", selected_ (assoc == NonAssoc)] ["(no associativity)"] 23 | , option_ [value_ "left", selected_ (assoc == LeftAssoc)] ["(left associative)"] 24 | , option_ [value_ "right", selected_ (assoc == RightAssoc)] ["(right associative)",rawHtml " "] 25 | ] 26 | , div_ [class_ "item-syntax-precedence"] 27 | ["(precedence level " 28 | , case selected of 29 | Just (S.SelectPrec j') | j == j' -> editor "number" (S.EditPrec j) textIn 30 | _ -> button "editable" "" (SetFocus (S.SelectPrec j)) [text $ MS.pack (show l)] 31 | , ")"] 32 | , div_ [class_ "item-syntax-controls"] 33 | (if alone then [] else [ iconButton "red" "Delete notation" "trash" (Act $ S.RemoveDecl j) ]) 34 | ] 35 | 36 | 37 | toAssoc :: MS.MisoString -> Associativity 38 | toAssoc "left" = LeftAssoc 39 | toAssoc "right" = RightAssoc 40 | toAssoc _ = NonAssoc 41 | -------------------------------------------------------------------------------- /View/Term.hs: -------------------------------------------------------------------------------- 1 | {-# LANGUAGE OverloadedStrings #-} 2 | module View.Term where 3 | import Miso 4 | import Terms 5 | import DisplayOptions 6 | import View.Utils 7 | import Data.List (intersperse) 8 | import qualified Miso.String as MS 9 | renderTerm opts trm = renderTermCtx [] opts trm 10 | 11 | renderTermCtx :: [Name] -> TermDisplayOptions -> Term -> View a 12 | renderTermCtx context opts trm = noActionsCoerce $ (renderTermCtxEditable Nothing context opts trm :: View (LocalAction Bool Bool)) 13 | 14 | renderTermCtxEditable :: (Eq focus, Eq action) 15 | => Maybe (MS.MisoString, Int -> focus, Int -> action, Maybe focus) 16 | -> [Name] -> TermDisplayOptions -> Term -> View (LocalAction focus action) 17 | renderTermCtxEditable editable context opts trm = renderTerm' True context trm 18 | where 19 | renderTerm' outer ctx (Lam (M v) t) = binder v (renderTerm' True (v : ctx) t) 20 | renderTerm' outer ctx other = renderTerm'' outer ctx other 21 | renderTerm'' outer ctx t 22 | | Lam _ _ <- t = multi $ parenthesise [renderTerm' False ctx t] 23 | | (x, ts, []) <- peelApTelescope' t = case x of 24 | LocalVar j 25 | | j >= length ctx -> boundName (MS.pack $ show j) 26 | | length ctx - j <= length context -> freevar (ctx !! j) 27 | | otherwise -> boundName (ctx !! j) 28 | MetaVar i -> case editable of 29 | Nothing -> metavar i 30 | Just (textIn, focus, act, selected) -> editableMath textIn (metavar i) (focus i) (act i) [] selected 31 | Const s False -> constant s 32 | Const s True -> constructor s 33 | 34 | | (Const n b, [], args) <- peelApTelescope' t 35 | , showInfixes opts 36 | , MS.count "_" n == length args 37 | = multi $ (if outer then id else parenthesise) $ intersperse space (infixTerms n args b) 38 | 39 | | (x, ts, args) <- peelApTelescope' t 40 | = multi $ (if outer then id else parenthesise) $ 41 | renderTerm'' False ctx x : space : intersperse space (map (renderTerm'' False ctx) args) 42 | where 43 | infixTerms str [] b | MS.null str = [] 44 | infixTerms str [] b = [if b then constructor str else constant str] 45 | infixTerms str (x : xs) b | Just ('_',str) <- MS.uncons str = renderTerm' False ctx x : infixTerms str xs b 46 | infixTerms str args b | (first, rest) <- MS.span (/= '_') str = (if b then constructor first else constant first) : infixTerms rest args b 47 | 48 | freevar v = inline "term-freevar" (name v) 49 | metavar v = inline "term-metavar" (name $ MS.pack ('?' : show v)) 50 | constant v = inline "term-const" (name v) 51 | constructor v = inline "term-constructor" (name v) 52 | boundName txt = inline "term-bound" (name txt) 53 | binder txt bdy = inline "term-binder" $ [boundName txt, ".", space, bdy] 54 | 55 | peelApTelescope' t | (t', args) <- peelApTelescope t = 56 | case t' of 57 | MetaVar i 58 | | not (showTeles opts) -> 59 | let (args1, args2) = span isAtom args 60 | in (MetaVar i, args1, args2) 61 | _ -> (t', [], args) 62 | where 63 | isAtom (LocalVar _) = True 64 | isAtom _ = False 65 | -------------------------------------------------------------------------------- /app.cabal: -------------------------------------------------------------------------------- 1 | name: holbert 2 | version: 0.6 3 | synopsis: An interactive proof assistant 4 | category: Web 5 | license: BSD3 6 | license-file: LICENSE 7 | build-type: Simple 8 | cabal-version: >=1.10 9 | 10 | flag mixfix 11 | description: Enable mixfix operator 12 | default: False 13 | 14 | executable app 15 | --if flag(mixfix) 16 | -- cpp-options: -DMIXFIX 17 | main-is: Main.hs 18 | other-modules: 19 | StringRep 20 | Prop 21 | ProofTree 22 | Terms 23 | Unification 24 | Editor 25 | Rule 26 | Heading 27 | SyntaxDecl 28 | Paragraph 29 | Controller 30 | Item 31 | DisplayOptions 32 | ImportExport 33 | View.Editor 34 | View.Term 35 | View.Utils 36 | View.ProofTree 37 | View.Prop 38 | View.Paragraph 39 | View.Heading 40 | View.SyntaxDecl 41 | View.Rule 42 | View.Item 43 | ghcjs-options: 44 | -dedupe 45 | build-depends: base, ghcjs-base == 0.2.1.0, aeson, hashable==1.3.5.0, text, miso, mtl, containers==0.6.8, optics-core, Earley, jsaddle == 0.9.8.2, unordered-containers==0.2.19.1 46 | default-language: Haskell2010 47 | -------------------------------------------------------------------------------- /browser-fs-access.min.js: -------------------------------------------------------------------------------- 1 | const e = (() => {if ("undefined" == typeof self) return !1;if ("top" in self && self !== top) try {top.window.document._ = 0;} catch (e) {return !1;}return "showOpenFilePicker" in self;})(),t = e ? Promise.resolve().then(function () {return l;}) : Promise.resolve().then(function () {return v;});async function n(...e) {return (await t).default(...e);}const r = e ? Promise.resolve().then(function () {return y;}) : Promise.resolve().then(function () {return b;});async function i(...e) {return (await r).default(...e);}const a = e ? Promise.resolve().then(function () {return m;}) : Promise.resolve().then(function () {return k;});async function o(...e) {return (await a).default(...e);}const s = async e => {const t = await e.getFile();return t.handle = e, t;};var c = async (e = [{}]) => {Array.isArray(e) || (e = [e]);const t = [];e.forEach((e, n) => {t[n] = { description: e.description || "Files", accept: {} }, e.mimeTypes ? e.mimeTypes.map(r => {t[n].accept[r] = e.extensions || [];}) : t[n].accept["*/*"] = e.extensions || [];});const n = await window.showOpenFilePicker({ id: e[0].id, startIn: e[0].startIn, types: t, multiple: e[0].multiple || !1, excludeAcceptAllOption: e[0].excludeAcceptAllOption || !1 }),r = await Promise.all(n.map(s));return e[0].multiple ? r : r[0];},l = { __proto__: null, default: c };function u(e) {function t(e) {if (Object(e) !== e) return Promise.reject(new TypeError(e + " is not an object."));var t = e.done;return Promise.resolve(e.value).then(function (e) {return { value: e, done: t };});}return u = function (e) {this.s = e, this.n = e.next;}, u.prototype = { s: null, n: null, next: function () {return t(this.n.apply(this.s, arguments));}, return: function (e) {var n = this.s.return;return void 0 === n ? Promise.resolve({ value: e, done: !0 }) : t(n.apply(this.s, arguments));}, throw: function (e) {var n = this.s.return;return void 0 === n ? Promise.reject(e) : t(n.apply(this.s, arguments));} }, new u(e);}const p = async (e, t, n = e.name, r) => {const i = [],a = [];var o,s = !1,c = !1;try {for (var l, d = function (e) {var t,n,r,i = 2;for ("undefined" != typeof Symbol && (n = Symbol.asyncIterator, r = Symbol.iterator); i--;) {if (n && null != (t = e[n])) return t.call(e);if (r && null != (t = e[r])) return new u(t.call(e));n = "@@asyncIterator", r = "@@iterator";}throw new TypeError("Object is not async iterable");}(e.values()); s = !(l = await d.next()).done; s = !1) {const o = l.value,s = `${n}/${o.name}`;"file" === o.kind ? a.push(o.getFile().then(t => (t.directoryHandle = e, t.handle = o, Object.defineProperty(t, "webkitRelativePath", { configurable: !0, enumerable: !0, get: () => s })))) : "directory" !== o.kind || !t || r && r(o) || i.push(p(o, t, s, r));}} catch (e) {c = !0, o = e;} finally {try {s && null != d.return && (await d.return());} finally {if (c) throw o;}}return [...(await Promise.all(i)).flat(), ...(await Promise.all(a))];};var d = async (e = {}) => {e.recursive = e.recursive || !1, e.mode = e.mode || "read";const t = await window.showDirectoryPicker({ id: e.id, startIn: e.startIn, mode: e.mode });return (await (await t.values()).next()).done ? [t] : p(t, e.recursive, void 0, e.skipDirectory);},y = { __proto__: null, default: d },f = async (e, t = [{}], n = null, r = !1, i = null) => {Array.isArray(t) || (t = [t]), t[0].fileName = t[0].fileName || "Untitled";const a = [];let o = null;if (e instanceof Blob && e.type ? o = e.type : e.headers && e.headers.get("content-type") && (o = e.headers.get("content-type")), t.forEach((e, t) => {a[t] = { description: e.description || "Files", accept: {} }, e.mimeTypes ? (0 === t && o && e.mimeTypes.push(o), e.mimeTypes.map(n => {a[t].accept[n] = e.extensions || [];})) : o ? a[t].accept[o] = e.extensions || [] : a[t].accept["*/*"] = e.extensions || [];}), n) try {await n.getFile();} catch (e) {if (n = null, r) throw e;}const s = n || (await window.showSaveFilePicker({ suggestedName: t[0].fileName, id: t[0].id, startIn: t[0].startIn, types: a, excludeAcceptAllOption: t[0].excludeAcceptAllOption || !1 }));!n && i && i(s);const c = await s.createWritable();if ("stream" in e) {const t = e.stream();return await t.pipeTo(c), s;}return "body" in e ? (await e.body.pipeTo(c), s) : (await c.write((await e)), await c.close(), s);},m = { __proto__: null, default: f },w = async (e = [{}]) => (Array.isArray(e) || (e = [e]), new Promise((t, n) => {const r = document.createElement("input");r.type = "file";const i = [...e.map(e => e.mimeTypes || []), ...e.map(e => e.extensions || [])].join();r.multiple = e[0].multiple || !1, r.accept = i || "", r.style.display = "none", document.body.append(r);const a = e => {"function" == typeof o && o(), t(e);},o = e[0].legacySetup && e[0].legacySetup(a, () => o(n), r),s = () => {window.removeEventListener("focus", s), r.remove();};r.addEventListener("click", () => {window.addEventListener("focus", s);}), r.addEventListener("change", () => {window.removeEventListener("focus", s), r.remove(), a(r.multiple ? Array.from(r.files) : r.files[0]);}), "showPicker" in HTMLInputElement.prototype ? r.showPicker() : r.click();})),v = { __proto__: null, default: w },h = async (e = [{}]) => (Array.isArray(e) || (e = [e]), e[0].recursive = e[0].recursive || !1, new Promise((t, n) => {const r = document.createElement("input");r.type = "file", r.webkitdirectory = !0;const i = e => {"function" == typeof a && a(), t(e);},a = e[0].legacySetup && e[0].legacySetup(i, () => a(n), r);r.addEventListener("change", () => {let t = Array.from(r.files);e[0].recursive ? e[0].recursive && e[0].skipDirectory && (t = t.filter(t => t.webkitRelativePath.split("/").every(t => !e[0].skipDirectory({ name: t, kind: "directory" })))) : t = t.filter(e => 2 === e.webkitRelativePath.split("/").length), i(t);}), "showPicker" in HTMLInputElement.prototype ? r.showPicker() : r.click();})),b = { __proto__: null, default: h },P = async (e, t = {}) => {Array.isArray(t) && (t = t[0]);const n = document.createElement("a");let r = e;"body" in e && (r = await async function (e, t) {const n = e.getReader(),r = new ReadableStream({ start: e => async function t() {return n.read().then(({ done: n, value: r }) => {if (!n) return e.enqueue(r), t();e.close();});}() }),i = new Response(r),a = await i.blob();return n.releaseLock(), new Blob([a], { type: t });}(e.body, e.headers.get("content-type"))), n.download = t.fileName || "Untitled", n.href = URL.createObjectURL((await r));const i = () => {"function" == typeof a && a();},a = t.legacySetup && t.legacySetup(i, () => a(), n);return n.addEventListener("click", () => {setTimeout(() => URL.revokeObjectURL(n.href), 3e4), i();}), n.click(), null;},k = { __proto__: null, default: P };export { i as directoryOpen, h as directoryOpenLegacy, d as directoryOpenModern, n as fileOpen, w as fileOpenLegacy, c as fileOpenModern, o as fileSave, P as fileSaveLegacy, f as fileSaveModern, e as supported }; -------------------------------------------------------------------------------- /cabal.config: -------------------------------------------------------------------------------- 1 | compiler: ghcjs -------------------------------------------------------------------------------- /cabal.project.local: -------------------------------------------------------------------------------- 1 | ignore-project: False 2 | compiler: ghcjs 3 | -------------------------------------------------------------------------------- /cmunfonts/README.md: -------------------------------------------------------------------------------- 1 | # computer-modern-web-font 2 | The Computer Modern LaTeX font for the web 3 | 4 | ## Example 5 | Take a look at this [example.html](https://cdn.rawgit.com/dreampulse/computer-modern-web-font/master/example.html). 6 | 7 | ## Usage 8 | 9 | Insert the `https://cdn.rawgit.com/dreampulse/computer-modern-web-font/master/fonts.css` css-stylesheet into your html header. 10 | 11 | ```html 12 | 13 | 14 | 15 | 16 | 21 | 22 | ``` 23 | 24 | ## Fonts 25 | 26 | The folowing font-familys are available: 27 | 28 | * `'Computer Modern Bright'` 29 | * `'Computer Modern Concrete'` 30 | * `'Computer Modern Sans'` 31 | * `'Computer Modern Serif'` 32 | * `'Computer Modern Typewriter'` 33 | 34 | ## Performance 35 | 36 | You can use the font for production websites with any amount of traffic. Files are served via MaxCDN's super fast global CDN. 37 | There is no traffic limits or throttling. 38 | -------------------------------------------------------------------------------- /cmunfonts/example.html: -------------------------------------------------------------------------------- 1 | 2 | 3 | 4 | 5 | example 6 | 7 | 8 | 25 | 26 | 27 |
28 |

Computer Modern Bright

29 |

Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet. Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet.

30 |
31 |
32 |

Computer Modern Concrete

33 |

Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet. Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet.

34 |
35 |
36 |

Computer Modern Sans

37 |

Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet. Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet.

38 |
39 |
40 |

Computer Modern Serif

41 |

Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet. Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet.

42 |
43 |
44 |

Computer Modern Typewriter

45 |

Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet. Lorem ipsum dolor sit amet, consetetur sadipscing elitr, sed diam nonumy eirmod tempor invidunt ut labore et dolore magna aliquyam erat, sed diam voluptua. At vero eos et accusam et justo duo dolores et ea rebum. Stet clita kasd gubergren, no sea takimata sanctus est Lorem ipsum dolor sit amet.

46 |
47 | 48 | -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/cmun-bright-semibold.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Bright Semibold'; 3 | src: url('cmunbsr.eot'); 4 | src: url('cmunbsr.eot?#iefix') format('embedded-opentype'), 5 | url('cmunbsr.woff') format('woff'), 6 | url('cmunbsr.ttf') format('truetype'), 7 | url('cmunbsr.svg#cmunbsr') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | @font-face { 13 | font-family: 'Computer Modern Bright Semibold'; 14 | src: url('cmunbso.eot'); 15 | src: url('cmunbso.eot?#iefix') format('embedded-opentype'), 16 | url('cmunbso.woff') format('woff'), 17 | url('cmunbso.ttf') format('truetype'), 18 | url('cmunbso.svg#cmunbso') format('svg'); 19 | font-weight: normal; 20 | font-style: italic; 21 | } 22 | 23 | -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/cmunbso.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright Semibold/cmunbso.eot -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/cmunbso.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright Semibold/cmunbso.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/cmunbso.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright Semibold/cmunbso.woff -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/cmunbsr.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright Semibold/cmunbsr.eot -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/cmunbsr.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright Semibold/cmunbsr.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Bright Semibold/cmunbsr.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright Semibold/cmunbsr.woff -------------------------------------------------------------------------------- /cmunfonts/font/Bright/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Bright/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmun-bright.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Bright'; 3 | src: url('cmunbmr.eot'); 4 | src: url('cmunbmr.eot?#iefix') format('embedded-opentype'), 5 | url('cmunbmr.woff') format('woff'), 6 | url('cmunbmr.ttf') format('truetype'), 7 | url('cmunbmr.svg#cmunbmr') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | @font-face { 13 | font-family: 'Computer Modern Bright'; 14 | src: url('cmunbbx.eot'); 15 | src: url('cmunbbx.eot?#iefix') format('embedded-opentype'), 16 | url('cmunbbx.woff') format('woff'), 17 | url('cmunbbx.ttf') format('truetype'), 18 | url('cmunbbx.svg#cmunbbx') format('svg'); 19 | font-weight: bold; 20 | font-style: normal; 21 | } 22 | 23 | @font-face { 24 | font-family: 'Computer Modern Bright'; 25 | src: url('cmunbmo.eot'); 26 | src: url('cmunbmo.eot?#iefix') format('embedded-opentype'), 27 | url('cmunbmo.woff') format('woff'), 28 | url('cmunbmo.ttf') format('truetype'), 29 | url('cmunbmo.svg#cmunbmo') format('svg'); 30 | font-weight: normal; 31 | font-style: italic; 32 | } 33 | 34 | @font-face { 35 | font-family: 'Computer Modern Bright'; 36 | src: url('cmunbxo.eot'); 37 | src: url('cmunbxo.eot?#iefix') format('embedded-opentype'), 38 | url('cmunbxo.woff') format('woff'), 39 | url('cmunbxo.ttf') format('truetype'), 40 | url('cmunbxo.svg#cmunbxo') format('svg'); 41 | font-weight: bold; 42 | font-style: italic; 43 | } 44 | 45 | 46 | -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbbx.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbbx.eot -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbbx.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbbx.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbbx.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbbx.woff -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbmo.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbmo.eot -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbmo.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbmo.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbmo.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbmo.woff -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbmr.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbmr.eot -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbmr.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbmr.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbmr.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbmr.woff -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbxo.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbxo.eot -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbxo.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbxo.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Bright/cmunbxo.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Bright/cmunbxo.woff -------------------------------------------------------------------------------- /cmunfonts/font/Classical Serif Italic/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Classical Serif Italic/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Classical Serif Italic/cmun-classical-serif-italic.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Classical Serif Italic'; 3 | src: url('cmunci.eot'); 4 | src: url('cmunci.eot?#iefix') format('embedded-opentype'), 5 | url('cmunci.woff') format('woff'), 6 | url('cmunci.ttf') format('truetype'), 7 | url('cmunci.svg#cmunci') format('svg'); 8 | font-weight: normal; 9 | font-style: italic; 10 | } 11 | 12 | -------------------------------------------------------------------------------- /cmunfonts/font/Classical Serif Italic/cmunci.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Classical Serif Italic/cmunci.eot -------------------------------------------------------------------------------- /cmunfonts/font/Classical Serif Italic/cmunci.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Classical Serif Italic/cmunci.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Classical Serif Italic/cmunci.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Classical Serif Italic/cmunci.woff -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmun-concrete.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Concrete'; 3 | src: url('cmunorm.eot'); 4 | src: url('cmunorm.eot?#iefix') format('embedded-opentype'), 5 | url('cmunorm.woff') format('woff'), 6 | url('cmunorm.ttf') format('truetype'), 7 | url('cmunorm.svg#cmunorm') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | 13 | @font-face { 14 | font-family: 'Computer Modern Concrete'; 15 | src: url('cmunobx.eot'); 16 | src: url('cmunobx.eot?#iefix') format('embedded-opentype'), 17 | url('cmunobx.woff') format('woff'), 18 | url('cmunobx.ttf') format('truetype'), 19 | url('cmunobx.svg#cmunobx') format('svg'); 20 | font-weight: bold; 21 | font-style: normal; 22 | } 23 | 24 | 25 | @font-face { 26 | font-family: 'Computer Modern Concrete'; 27 | src: url('cmunoti.eot'); 28 | src: url('cmunoti.eot?#iefix') format('embedded-opentype'), 29 | url('cmunoti.woff') format('woff'), 30 | url('cmunoti.ttf') format('truetype'), 31 | url('cmunoti.svg#cmunoti') format('svg'); 32 | font-weight: normal; 33 | font-style: italic; 34 | } 35 | 36 | 37 | @font-face { 38 | font-family: 'Computer Modern Concrete'; 39 | src: url('cmunobi.eot'); 40 | src: url('cmunobi.eot?#iefix') format('embedded-opentype'), 41 | url('cmunobi.woff') format('woff'), 42 | url('cmunobi.ttf') format('truetype'), 43 | url('cmunobi.svg#cmunobi') format('svg'); 44 | font-weight: bold; 45 | font-style: italic; 46 | } 47 | -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunobi.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunobi.eot -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunobi.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunobi.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunobi.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunobi.woff -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunobx.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunobx.eot -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunobx.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunobx.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunobx.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunobx.woff -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunorm.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunorm.eot -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunorm.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunorm.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunorm.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunorm.woff -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunoti.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunoti.eot -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunoti.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunoti.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Concrete/cmunoti.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Concrete/cmunoti.woff -------------------------------------------------------------------------------- /cmunfonts/font/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Sans Demi-Condensed/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Sans Demi-Condensed/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Sans Demi-Condensed/cmun-sans-demicondensed.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Sans Demi-Condensed'; 3 | src: url('cmunssdc.eot'); 4 | src: url('cmunssdc.eot?#iefix') format('embedded-opentype'), 5 | url('cmunssdc.woff') format('woff'), 6 | url('cmunssdc.ttf') format('truetype'), 7 | url('cmunssdc.svg#cmunssdc') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | -------------------------------------------------------------------------------- /cmunfonts/font/Sans Demi-Condensed/cmunssdc.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans Demi-Condensed/cmunssdc.eot -------------------------------------------------------------------------------- /cmunfonts/font/Sans Demi-Condensed/cmunssdc.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans Demi-Condensed/cmunssdc.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Sans Demi-Condensed/cmunssdc.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans Demi-Condensed/cmunssdc.woff -------------------------------------------------------------------------------- /cmunfonts/font/Sans/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Sans/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmun-sans.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Sans'; 3 | src: url('cmunss.eot'); 4 | src: url('cmunss.eot?#iefix') format('embedded-opentype'), 5 | url('cmunss.woff') format('woff'), 6 | url('cmunss.ttf') format('truetype'), 7 | url('cmunss.svg#cmunss') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | 13 | @font-face { 14 | font-family: 'Computer Modern Sans'; 15 | src: url('cmunsx.eot'); 16 | src: url('cmunsx.eot?#iefix') format('embedded-opentype'), 17 | url('cmunsx.woff') format('woff'), 18 | url('cmunsx.ttf') format('truetype'), 19 | url('cmunsx.svg#cmunsx') format('svg'); 20 | font-weight: bold; 21 | font-style: normal; 22 | } 23 | 24 | 25 | @font-face { 26 | font-family: 'Computer Modern Sans'; 27 | src: url('cmunsi.eot'); 28 | src: url('cmunsi.eot?#iefix') format('embedded-opentype'), 29 | url('cmunsi.woff') format('woff'), 30 | url('cmunsi.ttf') format('truetype'), 31 | url('cmunsi.svg#cmunsi') format('svg'); 32 | font-weight: normal; 33 | font-style: italic; 34 | } 35 | 36 | 37 | @font-face { 38 | font-family: 'Computer Modern Sans'; 39 | src: url('cmunso.eot'); 40 | src: url('cmunso.eot?#iefix') format('embedded-opentype'), 41 | url('cmunso.woff') format('woff'), 42 | url('cmunso.ttf') format('truetype'), 43 | url('cmunso.svg#cmunso') format('svg'); 44 | font-weight: bold; 45 | font-style: italic; 46 | } 47 | 48 | -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunsi.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunsi.eot -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunsi.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunsi.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunsi.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunsi.woff -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunso.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunso.eot -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunso.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunso.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunso.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunso.woff -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunss.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunss.eot -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunss.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunss.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunss.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunss.woff -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunsx.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunsx.eot -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunsx.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunsx.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Sans/cmunsx.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Sans/cmunsx.woff -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/cmun-serif-slanted.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Serif Slanted'; 3 | src: url('cmunsl.eot'); 4 | src: url('cmunsl.eot?#iefix') format('embedded-opentype'), 5 | url('cmunsl.woff') format('woff'), 6 | url('cmunsl.ttf') format('truetype'), 7 | url('cmunsl.svg#cmunsl') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | 13 | @font-face { 14 | font-family: 'Computer Modern Serif Slanted'; 15 | src: url('cmunbl.eot'); 16 | src: url('cmunbl.eot?#iefix') format('embedded-opentype'), 17 | url('cmunbl.woff') format('woff'), 18 | url('cmunbl.ttf') format('truetype'), 19 | url('cmunbl.svg#cmunbl') format('svg'); 20 | font-weight: bold; 21 | font-style: normal; 22 | } 23 | -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/cmunbl.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif Slanted/cmunbl.eot -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/cmunbl.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif Slanted/cmunbl.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/cmunbl.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif Slanted/cmunbl.woff -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/cmunsl.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif Slanted/cmunsl.eot -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/cmunsl.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif Slanted/cmunsl.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Serif Slanted/cmunsl.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif Slanted/cmunsl.woff -------------------------------------------------------------------------------- /cmunfonts/font/Serif/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Serif/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmun-serif.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Serif'; 3 | src: url('cmunrm.eot'); 4 | src: url('cmunrm.eot?#iefix') format('embedded-opentype'), 5 | url('cmunrm.woff') format('woff'), 6 | url('cmunrm.ttf') format('truetype'), 7 | url('cmunrm.svg#cmunrm') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | 13 | @font-face { 14 | font-family: 'Computer Modern Serif'; 15 | src: url('cmunbx.eot'); 16 | src: url('cmunbx.eot?#iefix') format('embedded-opentype'), 17 | url('cmunbx.woff') format('woff'), 18 | url('cmunbx.ttf') format('truetype'), 19 | url('cmunbx.svg#cmunbx') format('svg'); 20 | font-weight: bold; 21 | font-style: normal; 22 | } 23 | 24 | 25 | @font-face { 26 | font-family: 'Computer Modern Serif'; 27 | src: url('cmunti.eot'); 28 | src: url('cmunti.eot?#iefix') format('embedded-opentype'), 29 | url('cmunti.woff') format('woff'), 30 | url('cmunti.ttf') format('truetype'), 31 | url('cmunti.svg#cmunti') format('svg'); 32 | font-weight: normal; 33 | font-style: italic; 34 | } 35 | 36 | 37 | @font-face { 38 | font-family: 'Computer Modern Serif'; 39 | src: url('cmunbi.eot'); 40 | src: url('cmunbi.eot?#iefix') format('embedded-opentype'), 41 | url('cmunbi.woff') format('woff'), 42 | url('cmunbi.ttf') format('truetype'), 43 | url('cmunbi.svg#cmunbi') format('svg'); 44 | font-weight: bold; 45 | font-style: italic; 46 | } 47 | 48 | 49 | -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunbi.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunbi.eot -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunbi.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunbi.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunbi.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunbi.woff -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunbx.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunbx.eot -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunbx.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunbx.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunbx.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunbx.woff -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunrm.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunrm.eot -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunrm.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunrm.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunrm.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunrm.woff -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunti.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunti.eot -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunti.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunti.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Serif/cmunti.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Serif/cmunti.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/cmun-typewriter-light.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Typewriter Light'; 3 | src: url('cmunbtl.eot'); 4 | src: url('cmunbtl.eot?#iefix') format('embedded-opentype'), 5 | url('cmunbtl.woff') format('woff'), 6 | url('cmunbtl.ttf') format('truetype'), 7 | url('cmunbtl.svg#cmuntt') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | 13 | @font-face { 14 | font-family: 'Computer Modern Typewriter Light'; 15 | src: url('cmunbto.eot'); 16 | src: url('cmunbto.eot?#iefix') format('embedded-opentype'), 17 | url('cmunbto.woff') format('woff'), 18 | url('cmunbto.ttf') format('truetype'), 19 | url('cmunbto.svg#cmunbto') format('svg'); 20 | font-weight: normal; 21 | font-style: italic; 22 | } 23 | 24 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/cmunbtl.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Light/cmunbtl.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/cmunbtl.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Light/cmunbtl.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/cmunbtl.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Light/cmunbtl.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/cmunbto.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Light/cmunbto.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/cmunbto.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Light/cmunbto.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Light/cmunbto.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Light/cmunbto.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/cmun-typewriter-variable.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Typewriter Variable'; 3 | src: url('cmunvt.eot'); 4 | src: url('cmunvt.eot?#iefix') format('embedded-opentype'), 5 | url('cmunvt.woff') format('woff'), 6 | url('cmunvt.ttf') format('truetype'), 7 | url('cmunvt.svg#cmuntt') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | 13 | @font-face { 14 | font-family: 'Computer Modern Typewriter Variable'; 15 | src: url('cmunvi.eot'); 16 | src: url('cmunvi.eot?#iefix') format('embedded-opentype'), 17 | url('cmunvi.woff') format('woff'), 18 | url('cmunvi.ttf') format('truetype'), 19 | url('cmunvi.svg#cmunvi') format('svg'); 20 | font-weight: normal; 21 | font-style: italic; 22 | } 23 | 24 | 25 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/cmunvi.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Variable/cmunvi.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/cmunvi.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Variable/cmunvi.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/cmunvi.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Variable/cmunvi.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/cmunvt.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Variable/cmunvt.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/cmunvt.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Variable/cmunvt.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter Variable/cmunvt.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter Variable/cmunvt.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmun-typewriter.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Typewriter'; 3 | src: url('cmuntt.eot'); 4 | src: url('cmuntt.eot?#iefix') format('embedded-opentype'), 5 | url('cmuntt.woff') format('woff'), 6 | url('cmuntt.ttf') format('truetype'), 7 | url('cmuntt.svg#cmuntt') format('svg'); 8 | font-weight: normal; 9 | font-style: normal; 10 | } 11 | 12 | 13 | @font-face { 14 | font-family: 'Computer Modern Typewriter'; 15 | src: url('cmuntb.eot'); 16 | src: url('cmuntb.eot?#iefix') format('embedded-opentype'), 17 | url('cmuntb.woff') format('woff'), 18 | url('cmuntb.ttf') format('truetype'), 19 | url('cmuntb.svg#cmuntb') format('svg'); 20 | font-weight: bold; 21 | font-style: normal; 22 | } 23 | 24 | 25 | @font-face { 26 | font-family: 'Computer Modern Typewriter'; 27 | src: url('cmunit.eot'); 28 | src: url('cmunit.eot?#iefix') format('embedded-opentype'), 29 | url('cmunit.woff') format('woff'), 30 | url('cmunit.ttf') format('truetype'), 31 | url('cmunit.svg#cmunit') format('svg'); 32 | font-weight: normal; 33 | font-style: italic; 34 | } 35 | 36 | 37 | @font-face { 38 | font-family: 'Computer Modern Typewriter'; 39 | src: url('cmuntx.eot'); 40 | src: url('cmuntx.eot?#iefix') format('embedded-opentype'), 41 | url('cmuntx.woff') format('woff'), 42 | url('cmuntx.ttf') format('truetype'), 43 | url('cmuntx.svg#cmuntx') format('svg'); 44 | font-weight: bold; 45 | font-style: italic; 46 | } 47 | 48 | 49 | -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmunit.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmunit.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmunit.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmunit.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmunit.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmunit.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntb.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntb.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntb.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntb.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntb.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntb.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntt.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntt.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntt.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntt.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntt.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntt.woff -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntx.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntx.eot -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntx.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntx.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Typewriter/cmuntx.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Typewriter/cmuntx.woff -------------------------------------------------------------------------------- /cmunfonts/font/Upright Italic/OFL.txt: -------------------------------------------------------------------------------- 1 | Copyright (C) Authors of original metafont fonts: 2 | Donald Ervin Knuth (cm, concrete fonts) 3 | 1995, 1996, 1997 J"org Knappen, 1990, 1992 Norbert Schwarz (ec fonts) 4 | 1992-2006 A.Khodulev, O.Lapko, A.Berdnikov, V.Volovich (lh fonts) 5 | 1997-2005 Claudio Beccari (cb greek fonts) 6 | 2002 FUKUI Rei (tipa fonts) 7 | 2003-2005 Han The Thanh (Vietnamese fonts) 8 | 1996-2005 Walter Schmidt (cmbright fonts) 9 | 10 | Copyright (C) 2003-2009, Andrey V. Panov (panov@canopus.iacp.dvo.ru), 11 | with Reserved Font Family Name "Computer Modern Unicode fonts". 12 | 13 | This Font Software is licensed under the SIL Open Font License, Version 1.1. 14 | This license is copied below, and is also available with a FAQ at: 15 | http://scripts.sil.org/OFL 16 | 17 | 18 | ----------------------------------------------------------- 19 | SIL OPEN FONT LICENSE Version 1.1 - 26 February 2007 20 | ----------------------------------------------------------- 21 | 22 | PREAMBLE 23 | The goals of the Open Font License (OFL) are to stimulate worldwide 24 | development of collaborative font projects, to support the font creation 25 | efforts of academic and linguistic communities, and to provide a free and 26 | open framework in which fonts may be shared and improved in partnership 27 | with others. 28 | 29 | The OFL allows the licensed fonts to be used, studied, modified and 30 | redistributed freely as long as they are not sold by themselves. The 31 | fonts, including any derivative works, can be bundled, embedded, 32 | redistributed and/or sold with any software provided that any reserved 33 | names are not used by derivative works. The fonts and derivatives, 34 | however, cannot be released under any other type of license. The 35 | requirement for fonts to remain under this license does not apply 36 | to any document created using the fonts or their derivatives. 37 | 38 | DEFINITIONS 39 | "Font Software" refers to the set of files released by the Copyright 40 | Holder(s) under this license and clearly marked as such. This may 41 | include source files, build scripts and documentation. 42 | 43 | "Reserved Font Name" refers to any names specified as such after the 44 | copyright statement(s). 45 | 46 | "Original Version" refers to the collection of Font Software components as 47 | distributed by the Copyright Holder(s). 48 | 49 | "Modified Version" refers to any derivative made by adding to, deleting, 50 | or substituting -- in part or in whole -- any of the components of the 51 | Original Version, by changing formats or by porting the Font Software to a 52 | new environment. 53 | 54 | "Author" refers to any designer, engineer, programmer, technical 55 | writer or other person who contributed to the Font Software. 56 | 57 | PERMISSION & CONDITIONS 58 | Permission is hereby granted, free of charge, to any person obtaining 59 | a copy of the Font Software, to use, study, copy, merge, embed, modify, 60 | redistribute, and sell modified and unmodified copies of the Font 61 | Software, subject to the following conditions: 62 | 63 | 1) Neither the Font Software nor any of its individual components, 64 | in Original or Modified Versions, may be sold by itself. 65 | 66 | 2) Original or Modified Versions of the Font Software may be bundled, 67 | redistributed and/or sold with any software, provided that each copy 68 | contains the above copyright notice and this license. These can be 69 | included either as stand-alone text files, human-readable headers or 70 | in the appropriate machine-readable metadata fields within text or 71 | binary files as long as those fields can be easily viewed by the user. 72 | 73 | 3) No Modified Version of the Font Software may use the Reserved Font 74 | Name(s) unless explicit written permission is granted by the corresponding 75 | Copyright Holder. This restriction only applies to the primary font name as 76 | presented to the users. 77 | 78 | 4) The name(s) of the Copyright Holder(s) or the Author(s) of the Font 79 | Software shall not be used to promote, endorse or advertise any 80 | Modified Version, except to acknowledge the contribution(s) of the 81 | Copyright Holder(s) and the Author(s) or with their explicit written 82 | permission. 83 | 84 | 5) The Font Software, modified or unmodified, in part or in whole, 85 | must be distributed entirely under this license, and must not be 86 | distributed under any other license. The requirement for fonts to 87 | remain under this license does not apply to any document created 88 | using the Font Software. 89 | 90 | TERMINATION 91 | This license becomes null and void if any of the above conditions are 92 | not met. 93 | 94 | DISCLAIMER 95 | THE FONT SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 96 | EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO ANY WARRANTIES OF 97 | MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT 98 | OF COPYRIGHT, PATENT, TRADEMARK, OR OTHER RIGHT. IN NO EVENT SHALL THE 99 | COPYRIGHT HOLDER BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, 100 | INCLUDING ANY GENERAL, SPECIAL, INDIRECT, INCIDENTAL, OR CONSEQUENTIAL 101 | DAMAGES, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING 102 | FROM, OUT OF THE USE OR INABILITY TO USE THE FONT SOFTWARE OR FROM 103 | OTHER DEALINGS IN THE FONT SOFTWARE. 104 | -------------------------------------------------------------------------------- /cmunfonts/font/Upright Italic/README.txt: -------------------------------------------------------------------------------- 1 | This package was compiled by Christian Perfect (http://checkmyworking.com) from the Computer Modern Unicode fonts created by Andrey V. Panov (http://cm-unicode.sourceforge.net/) 2 | 3 | They're released under the SIL Open Font License. See OFL.txt and OFL-FAQ.txt for the terms. 4 | 5 | A demo page for these fonts was at http://www.checkmyworking.com/cm-web-fonts/ when I released them. I can only apologise, citizen of the future, if that address doesn't exist any more. 6 | -------------------------------------------------------------------------------- /cmunfonts/font/Upright Italic/cmun-upright-italic.css: -------------------------------------------------------------------------------- 1 | @font-face { 2 | font-family: 'Computer Modern Upright Italic'; 3 | src: url('cmunui.eot'); 4 | src: url('cmunui.eot?#iefix') format('embedded-opentype'), 5 | url('cmunui.woff') format('woff'), 6 | url('cmunui.uif') format('truetype'), 7 | url('cmunui.svg#cmunui') format('svg'); 8 | font-weight: normal; 9 | font-style: italic; 10 | } 11 | 12 | -------------------------------------------------------------------------------- /cmunfonts/font/Upright Italic/cmunui.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Upright Italic/cmunui.eot -------------------------------------------------------------------------------- /cmunfonts/font/Upright Italic/cmunui.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Upright Italic/cmunui.ttf -------------------------------------------------------------------------------- /cmunfonts/font/Upright Italic/cmunui.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/cmunfonts/font/Upright Italic/cmunui.woff -------------------------------------------------------------------------------- /cmunfonts/font/generator_config.txt: -------------------------------------------------------------------------------- 1 | # Font Squirrel Font-face Generator Configuration File 2 | # Upload this file to the generator to recreate the settings 3 | # you used to create these fonts. 4 | 5 | {"mode":"expert","formats":["ttf","woff","eotz"],"tt_instructor":"default","fix_vertical_metrics":"Y","fix_gasp":"xy","add_spaces":"Y","add_hyphens":"Y","fallback":"none","fallback_custom":"100","options_subset":"advanced","subset_range":["lowercase","uppercase","numbers","punctuation","currency","typographics","math","altpunctuation","accentedlower","accentedupper","diacriticals","albanian","bosnian","catalan","croatian","cyrillic","czech","danish","dutch","english","esperanto","estonian","faroese","french","german","greek","hebrew","hungarian","icelandic","italian","latvian","lithuanian","malagasy","maltese","norwegian","polish","portuguese","romanian","serbian","slovak","slovenian","spanish","swedish","turkish","ubasic","ucurrency","upunctuation"],"subset_custom":"","subset_custom_range":"","css_stylesheet":"stylesheet.css","filename_suffix":"","emsquare":"2048","spacing_adjustment":"0","rememberme":"Y"} -------------------------------------------------------------------------------- /cmunfonts/fonts.css: -------------------------------------------------------------------------------- 1 | @import url(./font/Bright/cmun-bright.css); 2 | @import url(./font/Bright Semibold/cmun-bright-semibold.css); 3 | @import url(./font/Classical Serif Italic/cmun-classical-serif-italic.css); 4 | @import url(./font/Concrete/cmun-concrete.css); 5 | @import url(./font/Sans/cmun-sans.css); 6 | @import url(./font/Sans Demi-Condensed/cmun-sans-demicondensed.css); 7 | @import url(./font/Serif/cmun-serif.css); 8 | @import url(./font/Serif Slanted/cmun-serif-slanted.css); 9 | @import url(./font/Typewriter/cmun-typewriter.css); 10 | @import url(./font/Typewriter Light/cmun-typewriter-light.css); 11 | @import url(./font/Typewriter Variable/cmun-typewriter-variable.css); 12 | @import url(./font/Upright Italic/cmun-upright-italic.css); 13 | -------------------------------------------------------------------------------- /cmunfonts/fonts.scss: -------------------------------------------------------------------------------- 1 | @import "./font/Bright/cmun-bright.css"; 2 | @import "./font/Bright Semibold/cmun-bright-semibold.css"; 3 | @import "./font/Classical Serif Italic/cmun-classical-serif-italic.css"; 4 | @import "./font/Concrete/cmun-concrete.css"; 5 | @import "./font/Sans/cmun-sans.css"; 6 | @import "./font/Sans Demi-Condensed/cmun-sans-demicondensed.css"; 7 | @import "./font/Serif/cmun-serif.css"; 8 | @import "./font/Serif Slanted/cmun-serif-slanted.css"; 9 | @import "./font/Typewriter/cmun-typewriter.css"; 10 | @import "./font/Typewriter Light/cmun-typewriter-light.css"; 11 | @import "./font/Typewriter Variable/cmun-typewriter-variable.css"; 12 | @import "./font/Upright Italic/cmun-upright-italic.css"; -------------------------------------------------------------------------------- /euler.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/euler.woff -------------------------------------------------------------------------------- /favicon.PNG: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/favicon.PNG -------------------------------------------------------------------------------- /split.min.js: -------------------------------------------------------------------------------- 1 | /*! Split.js - v1.6.0 */ 2 | !function(e,t){"object"==typeof exports&&"undefined"!=typeof module?module.exports=t():"function"==typeof define&&define.amd?define(t):(e=e||self).Split=t()}(this,(function(){"use strict";var e="undefined"!=typeof window?window:null,t=null===e,n=t?void 0:e.document,i=function(){return!1},r=t?"calc":["","-webkit-","-moz-","-o-"].filter((function(e){var t=n.createElement("div");return t.style.cssText="width:"+e+"calc(9px)",!!t.style.length})).shift()+"calc",s=function(e){return"string"==typeof e||e instanceof String},o=function(e){if(s(e)){var t=n.querySelector(e);if(!t)throw new Error("Selector "+e+" did not match a DOM element");return t}return e},a=function(e,t,n){var i=e[t];return void 0!==i?i:n},u=function(e,t,n,i){if(t){if("end"===i)return 0;if("center"===i)return e/2}else if(n){if("start"===i)return 0;if("center"===i)return e/2}return e},l=function(e,t){var i=n.createElement("div");return i.className="gutter gutter-"+t,i},c=function(e,t,n){var i={};return s(t)?i[e]=t:i[e]=r+"("+t+"% - "+n+"px)",i},h=function(e,t){var n;return(n={})[e]=t+"px",n};return function(r,s){if(void 0===s&&(s={}),t)return{};var d,f,v,m,g,p,y=r;Array.from&&(y=Array.from(y));var z=o(y[0]).parentNode,b=getComputedStyle?getComputedStyle(z):null,E=b?b.flexDirection:null,S=a(s,"sizes")||y.map((function(){return 100/y.length})),L=a(s,"minSize",100),_=Array.isArray(L)?L:y.map((function(){return L})),w=a(s,"expandToMin",!1),k=a(s,"gutterSize",10),x=a(s,"gutterAlign","center"),C=a(s,"snapOffset",30),M=a(s,"dragInterval",1),U=a(s,"direction","horizontal"),O=a(s,"cursor","horizontal"===U?"col-resize":"row-resize"),D=a(s,"gutter",l),A=a(s,"elementStyle",c),B=a(s,"gutterStyle",h);function j(e,t,n,i){var r=A(d,t,n,i);Object.keys(r).forEach((function(t){e.style[t]=r[t]}))}function F(){return p.map((function(e){return e.size}))}function R(e){return"touches"in e?e.touches[0][f]:e[f]}function T(e){var t=p[this.a],n=p[this.b],i=t.size+n.size;t.size=e/this.size*i,n.size=i-e/this.size*i,j(t.element,t.size,this._b,t.i),j(n.element,n.size,this._c,n.i)}function N(e){var t,n=p[this.a],r=p[this.b];this.dragging&&(t=R(e)-this.start+(this._b-this.dragOffset),M>1&&(t=Math.round(t/M)*M),t<=n.minSize+C+this._b?t=n.minSize+this._b:t>=this.size-(r.minSize+C+this._c)&&(t=this.size-(r.minSize+this._c)),T.call(this,t),a(s,"onDrag",i)())}function q(){var e=p[this.a].element,t=p[this.b].element,n=e.getBoundingClientRect(),i=t.getBoundingClientRect();this.size=n[d]+i[d]+this._b+this._c,this.start=n[v],this.end=n[m]}function H(e){var t=function(e){if(!getComputedStyle)return null;var t=getComputedStyle(e);if(!t)return null;var n=e[g];return 0===n?null:n-="horizontal"===U?parseFloat(t.paddingLeft)+parseFloat(t.paddingRight):parseFloat(t.paddingTop)+parseFloat(t.paddingBottom)}(z);if(null===t)return e;if(_.reduce((function(e,t){return e+t}),0)>t)return e;var n=0,i=[],r=e.map((function(r,s){var o=t*r/100,a=u(k,0===s,s===e.length-1,x),l=_[s]+a;return o0&&i[r]-n>0){var o=Math.min(n,i[r]-n);n-=o,s=e-o}return s/t*100}))}function I(){var t=p[this.a].element,r=p[this.b].element;this.dragging&&a(s,"onDragEnd",i)(F()),this.dragging=!1,e.removeEventListener("mouseup",this.stop),e.removeEventListener("touchend",this.stop),e.removeEventListener("touchcancel",this.stop),e.removeEventListener("mousemove",this.move),e.removeEventListener("touchmove",this.move),this.stop=null,this.move=null,t.removeEventListener("selectstart",i),t.removeEventListener("dragstart",i),r.removeEventListener("selectstart",i),r.removeEventListener("dragstart",i),t.style.userSelect="",t.style.webkitUserSelect="",t.style.MozUserSelect="",t.style.pointerEvents="",r.style.userSelect="",r.style.webkitUserSelect="",r.style.MozUserSelect="",r.style.pointerEvents="",this.gutter.style.cursor="",this.parent.style.cursor="",n.body.style.cursor=""}function W(t){if(!("button"in t)||0===t.button){var r=p[this.a].element,o=p[this.b].element;this.dragging||a(s,"onDragStart",i)(F()),t.preventDefault(),this.dragging=!0,this.move=N.bind(this),this.stop=I.bind(this),e.addEventListener("mouseup",this.stop),e.addEventListener("touchend",this.stop),e.addEventListener("touchcancel",this.stop),e.addEventListener("mousemove",this.move),e.addEventListener("touchmove",this.move),r.addEventListener("selectstart",i),r.addEventListener("dragstart",i),o.addEventListener("selectstart",i),o.addEventListener("dragstart",i),r.style.userSelect="none",r.style.webkitUserSelect="none",r.style.MozUserSelect="none",r.style.pointerEvents="none",o.style.userSelect="none",o.style.webkitUserSelect="none",o.style.MozUserSelect="none",o.style.pointerEvents="none",this.gutter.style.cursor=O,this.parent.style.cursor=O,n.body.style.cursor=O,q.call(this),this.dragOffset=R(t)-this.end}}"horizontal"===U?(d="width",f="clientX",v="left",m="right",g="clientWidth"):"vertical"===U&&(d="height",f="clientY",v="top",m="bottom",g="clientHeight"),S=H(S);var X=[];function Y(e){var t=e.i===X.length,n=t?X[e.i-1]:X[e.i];q.call(n);var i=t?n.size-e.minSize-n._c:e.minSize+n._b;T.call(n,i)}return(p=y.map((function(e,t){var n,i={element:o(e),size:S[t],minSize:_[t],i:t};if(t>0&&((n={a:t-1,b:t,dragging:!1,direction:U,parent:z})._b=u(k,t-1==0,!1,x),n._c=u(k,!1,t===y.length-1,x),"row-reverse"===E||"column-reverse"===E)){var r=n.a;n.a=n.b,n.b=r}if(t>0){var s=D(t,U,i.element);!function(e,t,n){var i=B(d,t,n);Object.keys(i).forEach((function(t){e.style[t]=i[t]}))}(s,k,t),n._a=W.bind(n),s.addEventListener("mousedown",n._a),s.addEventListener("touchstart",n._a),z.insertBefore(s,i.element),n.gutter=s}return j(i.element,i.size,u(k,0===t,t===y.length-1,x),t),t>0&&X.push(n),i}))).forEach((function(e){var t=e.element.getBoundingClientRect()[d];t0){var i=X[n-1],r=p[i.a],s=p[i.b];r.size=t[n-1],s.size=e,j(r.element,r.size,i._b,r.i),j(s.element,s.size,i._c,s.i)}}))},getSizes:F,collapse:function(e){Y(p[e])},destroy:function(e,t){X.forEach((function(n){if(!0!==t?n.parent.removeChild(n.gutter):(n.gutter.removeEventListener("mousedown",n._a),n.gutter.removeEventListener("touchstart",n._a)),!0!==e){var i=A(d,n.a.size,n._b);Object.keys(i).forEach((function(e){p[n.a].element.style[e]="",p[n.b].element.style[e]=""}))}}))},parent:z,pairs:X}}})); 3 | //# sourceMappingURL=split.min.js.map 4 | -------------------------------------------------------------------------------- /typicons.eot: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/typicons.eot -------------------------------------------------------------------------------- /typicons.ttf: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/typicons.ttf -------------------------------------------------------------------------------- /typicons.woff: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/liamoc/holbert/2226316d3fab3504aa9645b3eacf4e0833b17f4d/typicons.woff --------------------------------------------------------------------------------