Rename {hdoc => textphile}
authorJulien Moutinho <julm+hdoc@autogeree.net>
Thu, 5 Mar 2020 02:03:45 +0000 (03:03 +0100)
committerJulien Moutinho <julm+hdoc@autogeree.net>
Thu, 5 Mar 2020 02:03:45 +0000 (03:03 +0100)
65 files changed:
Hdoc/TCT.hs [deleted file]
exe/HLint.hs [deleted symlink]
exe/cli/HLint.hs [deleted symlink]
exe/cli/Main.hs [deleted file]
src/Control/HLint.hs [moved from Control/HLint.hs with 100% similarity]
src/Control/Monad/HLint.hs [moved from Control/Monad/HLint.hs with 100% similarity]
src/Control/Monad/Utils.hs [moved from Control/Monad/Utils.hs with 99% similarity]
src/Text/Blaze/DTC.hs [moved from Text/Blaze/DTC.hs with 99% similarity]
src/Text/Blaze/DTC/Attributes.hs [moved from Text/Blaze/DTC/Attributes.hs with 100% similarity]
src/Text/Blaze/DTC/HLint.hs [moved from Hdoc/DTC/Analyze/HLint.hs with 100% similarity]
src/Text/Blaze/HLint.hs [moved from Hdoc/DTC/HLint.hs with 100% similarity]
src/Text/Blaze/HTML5.hs [moved from Text/Blaze/HTML5.hs with 100% similarity]
src/Text/Blaze/Utils.hs [moved from Text/Blaze/Utils.hs with 100% similarity]
src/Text/Blaze/XML.hs [moved from Text/Blaze/XML.hs with 93% similarity]
src/Text/HLint.hs [moved from Hdoc/DTC/Read/HLint.hs with 100% similarity]
src/Textphile/DTC/Analyze/Check.hs [moved from Hdoc/DTC/Analyze/Check.hs with 97% similarity]
src/Textphile/DTC/Analyze/Collect.hs [moved from Hdoc/DTC/Analyze/Collect.hs with 98% similarity]
src/Textphile/DTC/Analyze/HLint.hs [moved from Hdoc/DTC/Write/HLint.hs with 100% similarity]
src/Textphile/DTC/Analyze/Index.hs [moved from Hdoc/DTC/Analyze/Index.hs with 98% similarity]
src/Textphile/DTC/Document.hs [moved from Hdoc/DTC/Document.hs with 98% similarity]
src/Textphile/DTC/HLint.hs [moved from Hdoc/HLint.hs with 100% similarity]
src/Textphile/DTC/Read/HLint.hs [moved from Hdoc/RNC/HLint.hs with 100% similarity]
src/Textphile/DTC/Read/TCT.hs [moved from Hdoc/DTC/Read/TCT.hs with 97% similarity]
src/Textphile/DTC/Sym.hs [moved from Hdoc/DTC/Sym.hs with 98% similarity]
src/Textphile/DTC/Write/HLint.hs [moved from Hdoc/TCT/HLint.hs with 100% similarity]
src/Textphile/DTC/Write/HTML5.hs [moved from Hdoc/DTC/Write/HTML5.hs with 96% similarity]
src/Textphile/DTC/Write/HTML5/Base.hs [moved from Hdoc/DTC/Write/HTML5/Base.hs with 95% similarity]
src/Textphile/DTC/Write/HTML5/Error.hs [moved from Hdoc/DTC/Write/HTML5/Error.hs with 94% similarity]
src/Textphile/DTC/Write/HTML5/Ident.hs [moved from Hdoc/DTC/Write/HTML5/Ident.hs with 94% similarity]
src/Textphile/DTC/Write/HTML5/Judgment.hs [moved from Hdoc/DTC/Write/HTML5/Judgment.hs with 97% similarity]
src/Textphile/DTC/Write/Plain.hs [moved from Hdoc/DTC/Write/Plain.hs with 97% similarity]
src/Textphile/DTC/Write/XML.hs [moved from Hdoc/DTC/Write/XML.hs with 98% similarity]
src/Textphile/HLint.hs [moved from Hdoc/TCT/Read/HLint.hs with 100% similarity]
src/Textphile/RNC.hs [moved from Hdoc/RNC.hs with 90% similarity]
src/Textphile/RNC/HLint.hs [moved from Hdoc/TCT/Write/HLint.hs with 100% similarity]
src/Textphile/TCT.hs [new file with mode: 0644]
src/Textphile/TCT/Cell.hs [moved from Hdoc/TCT/Cell.hs with 97% similarity]
src/Textphile/TCT/Debug.hs [moved from Hdoc/TCT/Debug.hs with 99% similarity]
src/Textphile/TCT/Elem.hs [moved from Hdoc/TCT/Elem.hs with 94% similarity]
src/Textphile/TCT/HLint.hs [moved from Text/Blaze/DTC/HLint.hs with 100% similarity]
src/Textphile/TCT/Read.hs [moved from Hdoc/TCT/Read.hs with 93% similarity]
src/Textphile/TCT/Read/Cell.hs [moved from Hdoc/TCT/Read/Cell.hs with 98% similarity]
src/Textphile/TCT/Read/Elem.hs [moved from Hdoc/TCT/Read/Elem.hs with 96% similarity]
src/Textphile/TCT/Read/HLint.hs [moved from Text/Blaze/HLint.hs with 100% similarity]
src/Textphile/TCT/Read/Token.hs [moved from Hdoc/TCT/Read/Token.hs with 98% similarity]
src/Textphile/TCT/Read/Tree.hs [moved from Hdoc/TCT/Read/Tree.hs with 96% similarity]
src/Textphile/TCT/Tree.hs [moved from Hdoc/TCT/Tree.hs with 99% similarity]
src/Textphile/TCT/Utils.hs [moved from Hdoc/TCT/Utils.hs with 91% similarity]
src/Textphile/TCT/Write/HLint.hs [moved from Text/HLint.hs with 100% similarity]
src/Textphile/TCT/Write/HTML5.hs [moved from Hdoc/TCT/Write/HTML5.hs with 98% similarity]
src/Textphile/TCT/Write/Plain.hs [moved from Hdoc/TCT/Write/Plain.hs with 98% similarity]
src/Textphile/TCT/Write/XML.hs [moved from Hdoc/TCT/Write/XML.hs with 98% similarity]
src/Textphile/Utils.hs [moved from Hdoc/Utils.hs with 98% similarity]
src/Textphile/XML.hs [moved from Hdoc/XML.hs with 94% similarity]
src/style/dtc-errors.css [moved from style/dtc-errors.css with 100% similarity]
src/style/dtc-errors.js [moved from style/dtc-errors.js with 100% similarity]
src/style/dtc-html5.css [moved from style/dtc-html5.css with 100% similarity]
src/style/dtc-html5.js [new file with mode: 0644]
src/style/dtc-index.css [moved from style/dtc-index.css with 100% similarity]
src/style/dtc-judgment.css [moved from style/dtc-judgment.css with 100% similarity]
src/style/dtc-table.css [moved from style/dtc-table.css with 100% similarity]
src/style/dtc-xml.css [moved from style/dtc-xml.css with 100% similarity]
src/style/tct-html5.css [moved from style/tct-html5.css with 100% similarity]
stack.yaml
textphile.cabal [moved from hdoc.cabal with 73% similarity]

diff --git a/Hdoc/TCT.hs b/Hdoc/TCT.hs
deleted file mode 100644 (file)
index 9f127bd..0000000
+++ /dev/null
@@ -1,11 +0,0 @@
-module Hdoc.TCT
- ( module Hdoc.TCT.Cell
- , module Hdoc.TCT.Tree
- , module Hdoc.TCT.Elem
- , module Hdoc.TCT.Read
- ) where
-
-import Hdoc.TCT.Cell
-import Hdoc.TCT.Tree
-import Hdoc.TCT.Elem
-import Hdoc.TCT.Read
diff --git a/exe/HLint.hs b/exe/HLint.hs
deleted file mode 120000 (symlink)
index ab18269..0000000
+++ /dev/null
@@ -1 +0,0 @@
-../HLint.hs
\ No newline at end of file
diff --git a/exe/cli/HLint.hs b/exe/cli/HLint.hs
deleted file mode 120000 (symlink)
index ab18269..0000000
+++ /dev/null
@@ -1 +0,0 @@
-../HLint.hs
\ No newline at end of file
diff --git a/exe/cli/Main.hs b/exe/cli/Main.hs
deleted file mode 100644 (file)
index 157de4f..0000000
+++ /dev/null
@@ -1,682 +0,0 @@
-{-# LANGUAGE AllowAmbiguousTypes #-}
-{-# LANGUAGE DuplicateRecordFields #-}
-{-# LANGUAGE ExistentialQuantification #-}
-{-# LANGUAGE FlexibleContexts #-}
-{-# LANGUAGE OverloadedLists #-}
-{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE TupleSections #-}
-{-# LANGUAGE TypeApplications #-}
-{-# LANGUAGE TypeFamilies #-}
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-module Main where
-
--- import Data.Reflection (reify, Reifies(..))
--- import qualified Data.Text.IO as Text
-import Control.Applicative (pure)
-import Control.Monad (Monad(..), when)
-import Data.Bool
-import Data.Default.Class (Default(..))
-import Data.Either (Either(..))
-import Data.Eq (Eq(..))
-import Data.Foldable as Foldable (Foldable(..))
-import Data.Function (($), (.))
-import Data.Functor ((<$>))
-import Data.List.NonEmpty (NonEmpty(..))
-import Data.Locale
-import Data.Maybe (Maybe(..), fromMaybe, maybe)
-import Data.Monoid (Monoid(..))
-import Data.Ord (Ord(..))
-import Data.Semigroup (Semigroup(..))
-import Data.String (String, IsString(..))
-import Data.Void (Void)
-import GHC.Exts (IsList(..))
-import Prelude (error)
-import System.FilePath as FilePath
-import System.IO (IO, FilePath)
-import Text.Show (Show(..))
-import qualified Data.ByteString as BS
-import qualified Data.Char as Char
-import qualified Data.List as List
-import qualified Data.Map.Strict as Map
-import qualified Data.Set as Set
-import qualified Data.Text as Text
-import qualified Data.Text.Lazy as TL
-import qualified Data.Text.Lazy.IO as TL
-import qualified Data.TreeSeq.Strict as Tree
-import qualified Data.Version as Version
-import qualified Paths_hdoc as Hdoc
-import qualified Symantic.RNC.Write as RNC
-import qualified System.Directory as IO
-import qualified System.Environment as Env
-import qualified System.IO as IO
-import qualified Text.Blaze.Renderer.Utf8 as Blaze
-import qualified Text.Blaze.Utils as Blaze
-import qualified Text.Megaparsec as P
-
-import qualified Hdoc.Utils           as FS
-import qualified Hdoc.TCT             as TCT
-import qualified Hdoc.TCT.Write.HTML5 as TCT
-import qualified Hdoc.TCT.Write.Plain as TCT
-import qualified Hdoc.TCT.Write.XML   as TCT
-import qualified Hdoc.DTC.Read.TCT    as DTC
-import qualified Hdoc.DTC.Sym         as DTC
-import qualified Hdoc.DTC.Write.HTML5 as DTC
-import qualified Hdoc.DTC.Write.XML   as DTC
-import qualified Text.Blaze.DTC           as Blaze.DTC
-import qualified Text.Blaze.HTML5         as Blaze.HTML5
-
-import Symantic.CLI hiding (main)
-import qualified Symantic.CLI as CLI
-import qualified Language.Symantic.Document.Term.IO as Doc
-
-import qualified Symantic.CLI.Plain as Plain
-import qualified Symantic.CLI.Help  as Help
-import qualified Symantic.CLI.Read  as Read
-
-version :: TL.Text
-version = "hdoc-" <> TL.pack (Version.showVersion Hdoc.version)
-
-main :: IO ()
-main = do
-       lang <- getLang
-       args <- Env.getArgs
-       readArgs lang args >>= \case
-        Nothing -> return ()
-        Just (Left  err) -> onExit err
-        Just (Right cmd) -> onCommand cmd
-
-readArgs ::
- forall d.
- Plain.Doc d =>
- Lang -> [String] -> IO.IO (Maybe (Either (Exit (Doc d)) Command))
-readArgs lang args =
-       case
-               Read.readArgs (cli (loqualize lang) lang) $
-               Read.Args $ Read.Arg <$> ("hdoc":args) of
-        Right a -> return $ Just $ Right a
-        Left err ->
-               case P.bundleErrors err of
-                P.FancyError o es :| _ ->
-                       case Set.toList es of
-                        [P.ErrorCustom (Read.ErrorRead e)] ->
-                               case e of
-                                Exit_Error ee -> do
-                                       IO.hPutStr IO.stderr $
-                                               P.parseErrorPretty @Read.Args @(Read.ErrorRead Error) $
-                                               P.FancyError o $ Set.singleton $ P.ErrorCustom $
-                                               Read.ErrorRead ee
-                                       return Nothing
-                                _ -> return $ Just $ Left e
-                        _ -> return Nothing
-                P.TrivialError o e es :| _ -> do
-                       IO.hPutStr IO.stderr $
-                               P.parseErrorPretty @Read.Args @Void $
-                               P.TrivialError o e es
-                       return Nothing
-
--- * Type 'Exit'
-data Exit d
- =   Exit_Help d
- |   Exit_Version
- |   Exit_License (Loq d)
- |   Exit_Error Error
- deriving Show
-instance Show (Loqualization q) where
-       show _ = "Loqualization"
-
-onExit :: Exit (Doc Doc.TermIO) -> IO ()
-onExit (Exit_Help d) =
-       Doc.runTermIO IO.stdout $
-       Doc.withBreakable (Just 80) (runDoc d) <>
-       Doc.newline
-onExit Exit_Version =
-       TL.putStrLn version
-onExit (Exit_License (Loqualization l)) =
-       Doc.runTermIO IO.stdout $
-       runDoc $
-       l10n_license l
-onExit Exit_Error{} =
-       return ()
-
--- ** Type 'Error'
-newtype Error
- =   Error_Locale String
- deriving Show
-
--- * Type 'Command'
-data Command
- =   Command_Source  CommandSource
- |   Command_Compile CommandCompile
- |   Command_Schema  CommandSchema
- deriving (Show)
-
-onCommand :: Command -> IO ()
-onCommand cmd@(Command_Source CommandSource{..}) = do
-       IO.hPrint IO.stderr cmd
-       TCT.readTCT source_input >>= \case
-        Left err -> error $ show err
-        Right tct -> do
-               when source_dump_tct $
-                       FS.writeFile (source_output-<.>"tct.dump") $
-                               TL.pack $ Tree.prettyTrees tct
-               case source_format of
-                CommandSourceFormat_Plain ->
-                       FS.writeFile source_output $
-                       TCT.writePlain tct
-                CommandSourceFormat_HTML5 ->
-                       FS.withFile source_output IO.WriteMode $ \h ->
-                               Blaze.renderMarkupToByteStringIO (BS.hPutStr h) $
-                               TCT.writeHTML5 tct
-onCommand cmd@(Command_Compile cmdComp@CommandCompile{..}) = do
-       IO.hPrint IO.stderr cmd
-       TCT.readTCT compile_input >>= \case
-        Left err -> error $ show err
-        Right tct -> do
-               when compile_dump_tct $ do
-                       FS.writeFile (compile_output-<.>"tct.dump") $
-                               TL.pack $ Tree.prettyTrees tct
-               let xml = TCT.writeXML tct
-               when compile_dump_xml $ do
-                       FS.writeFile (compile_output-<.>"xml.dump") $
-                               TL.pack $ Tree.prettyTrees xml
-               case DTC.readDTC xml of
-                Left err -> do
-                       FS.removeFile $ compile_output-<.>"deps"
-                       error $ List.unlines $ Foldable.toList $ P.parseErrorPretty <$> P.bundleErrors err
-                Right dtc -> do
-                       when compile_dump_deps $ do
-                               writeDependencies cmdComp tct
-                       when compile_dump_xml $ do
-                               FS.writeFile (compile_output-<.>"dtc.dump") $
-                                       TL.pack $ show dtc
-                       case compile_format of
-                        CommandCompileFormat_XML ->
-                               FS.withFile compile_output IO.WriteMode $ \h ->
-                                       Blaze.prettyMarkupIO Blaze.DTC.isInlinedElement (BS.hPutStr h) $
-                                       DTC.writeXML compile_locale dtc
-                        CommandCompileFormat_HTML5{..} -> do
-                               config_css <- installFile compile_html5_output_css $ "style"</>"dtc-html5.css"
-                               config_js  <- installFile compile_html5_output_js  $ "style"</>"dtc-html5.js"
-                               let conf = DTC.Config
-                                        { DTC.config_css
-                                        , DTC.config_js
-                                        , DTC.config_locale    = compile_locale
-                                        , DTC.config_generator = version
-                                        }
-                               FS.withFile compile_output IO.WriteMode $ \h -> do
-                                       html <- DTC.writeHTML5 conf dtc
-                                       Blaze.prettyMarkupIO
-                                        Blaze.HTML5.isInlinedElement
-                                        (BS.hPutStr h)
-                                        html
-                               where
-                               installFile out name = do
-                                       dataDir <- Hdoc.getDataDir
-                                       let src = dataDir</>name
-                                       case out of
-                                        Nothing -> Right <$> FS.readFile src
-                                        Just "" -> return $ Left ""
-                                        Just dst -> do
-                                               IO.createDirectoryIfMissing True $ FilePath.takeDirectory dst
-                                               IO.copyFile src dst
-                                               return $ Left dst
-onCommand Command_Schema{} =
-       TL.hPutStrLn IO.stdout $
-               RNC.writeRNC DTC.schema DTC.schema
-
-writeDependencies :: CommandCompile -> TCT.Roots -> IO ()
-writeDependencies CommandCompile{..} tct =
-       let dir = FilePath.takeDirectory compile_input in
-       FS.writeFile (compile_input-<.>"deps") $
-               foldMap (TL.pack . (("\n" <>) . FilePath.normalise))
-                ((dir </>) <$> TCT.dependencies tct) <>
-               "\n"
-
--- ** Type 'CommandSource'
-data CommandSource
- =   CommandSource
- {   source_output    :: FilePath
- ,   source_dump_tct  :: Bool
- ,   source_format    :: CommandSourceFormat
- ,   source_input     :: FilePath
- }
- deriving (Show)
-
--- *** Type 'CommandSourceFormat'
-data CommandSourceFormat
- =   CommandSourceFormat_Plain
- |   CommandSourceFormat_HTML5
- deriving (Show)
-instance Default CommandSourceFormat where
-       def = CommandSourceFormat_Plain
-
--- *** Type 'CommandSourceDump'
-data CommandSourceDump
- =   CommandSourceDump_TCT
- |   CommandSourceDump_XML
- deriving (Eq, Ord, Show)
-
--- ** Type 'CommandCompile'
-data CommandCompile
- =   CommandCompile
- {   compile_output    :: FilePath
- ,   compile_locale    :: Lang
- ,   compile_dump_tct  :: Bool
- ,   compile_dump_xml  :: Bool
- ,   compile_dump_deps :: Bool
- ,   compile_format    :: CommandCompileFormat
- ,   compile_input     :: FilePath
- -- ,   compile_dump     :: Set CommandCompileDump
- }
- deriving (Show)
-
--- *** Type 'CommandCompileFormat'
-data CommandCompileFormat
- =   CommandCompileFormat_HTML5
-     { compile_html5_output_css :: Maybe FilePath
-     , compile_html5_output_js  :: Maybe FilePath
-     , compile_html5_dump_dtc   :: Bool
-     }
- |   CommandCompileFormat_XML
-     {
-     }
- deriving (Show)
-instance Default CommandCompileFormat where
-       def = CommandCompileFormat_HTML5
-        { compile_html5_output_css = def
-        , compile_html5_output_js  = def
-        , compile_html5_dump_dtc   = False
-        }
-
--- *** Type 'CommandCompileDump'
-data CommandCompileDump
- =   CommandCompileDump_TCT
- |   CommandCompileDump_XML
- |   CommandCompileDump_DTC
- |   CommandCompileDump_Deps
- deriving (Eq, Ord, Show)
-
--- ** Type 'CommandSchema'
-data CommandSchema
- =   CommandSchema
- deriving (Show)
-
--- * Class 'CLI'
-class
- ( Sym_Fun repr
- , Sym_App repr
- , Sym_Alt repr
- , Sym_AltApp repr
- , Sym_Help d repr
- , Sym_Rule repr
- , Sym_Permutation repr
- , Sym_Command repr
- , Sym_Option repr
- , Sym_Exit repr
- , Plain.Doc d
- -- , Reifies lang
- ) => CLI d repr where
-       cli :: Loq d -> Lang -> repr (Exit d) ArgCommand Command
-       cli loq@(Loqualization l) lang =
-               help @d (l10n_cli l) $
-               CLI.main "hdoc" $ opts **> cmds
-               where
-               opts =
-                       runPermutation $
-                       (\_ _ -> ())
-                        <<$?   option_help loq (help_usage $ cli loq lang)
-                        <<|?>> option_version loq
-                        <<|?>> option_license loq
-               cmds =
-                       Command_Source  <$$> command_source  loq <||>
-                       Command_Compile <$$> command_compile loq lang <||>
-                       Command_Schema  <$$> command_schema  loq
-       
-       option_help :: Loq d -> d -> ((), repr (Exit d) ArgOption ())
-       option_help (Loqualization l) d =
-               ((),) $
-               help @d (l10n_help_opt_help l) $
-               opt (OptionName 'h' "help") $
-               exit $ Exit_Help d
-       option_version :: Loq d -> ((), repr (Exit d) ArgOption ())
-       option_version (Loqualization l) = ((),) $
-               help @d (l10n_help_version l) $
-               long "version" $ exit $ Exit_Version
-       option_license :: Loq d -> ((), repr (Exit d) ArgOption ())
-       option_license loq@(Loqualization l) = ((),) $
-               help @d (l10n_help_license l) $
-               long "license" $ exit $ Exit_License loq
-       {-
-       option_input :: Loq d -> (FilePath, repr (Exit d) ArgOption FilePath)
-       option_input (Loqualization l) =
-               (mempty,) $
-               help @d (l10n_help_opt_input l) $
-               opt (OptionName 'i' "input") $
-               string $ l10n_var_file l
-       -}
-       option_output :: Loq d -> (FilePath, repr (Exit d) ArgOption FilePath)
-       option_output (Loqualization l) =
-               (mempty,) $
-               help @d (l10n_help_opt_output l) $
-               opt (OptionName 'o' "output") $
-               string $ l10n_var_file l
-       option_lang :: Loq d -> Lang -> (Lang, repr (Exit d) ArgOption Lang)
-       option_lang (Loqualization l) lang =
-               (lang,) $
-               help @d (l10n_help_opt_lang l) $
-               long "lang" $
-               var (l10n_var_locale l) $ \s ->
-                       maybe (Left $ Exit_Error $ Error_Locale s) Right $
-                       Map.lookup (Text.pack s) $
-                       locales @Langs
-       option_dump_tct :: Loq d -> (Bool, repr (Exit d) ArgOption Bool)
-       option_dump_tct (Loqualization l) =
-               help @d (l10n_help_opt_dump_tct l) <$>
-               flag (OptionNameLong "dump-tct")
-       option_dump_xml :: Loq d -> (Bool, repr (Exit d) ArgOption Bool)
-       option_dump_xml (Loqualization l) =
-               help @d (l10n_help_opt_dump_xml l) <$>
-               flag (OptionNameLong "dump-xml")
-       option_dump_deps :: Loq d -> (Bool, repr (Exit d) ArgOption Bool)
-       option_dump_deps (Loqualization l) =
-               help @d (l10n_help_opt_dump_deps l) <$>
-               flag (OptionNameLong "dump-deps")
-       option_dump_dtc :: Loq d -> (Bool, repr (Exit d) ArgOption Bool)
-       option_dump_dtc (Loqualization l) =
-               help @d (l10n_help_opt_dump_dtc l) <$>
-               flag (OptionNameLong "dump-dtc")
-       
-       command_source :: Loq d -> repr (Exit d) ArgCommand CommandSource
-       command_source loq@(Loqualization l) =
-               help @d (l10n_help_command_source l) $
-               command "source" $
-               (runPermutation $
-                       CommandSource
-                        <<$?   option_help loq (help_usage $ command_source loq)
-                        <<|?>> option_output   loq
-                        <<|?>> option_dump_tct loq)
-                <**> (command_source_plain loq
-                 <||> command_source_html5 loq)
-                <**> string (l10n_var_file l)
-       command_source_plain :: Loq d -> repr (Exit d) ArgCommand CommandSourceFormat
-       command_source_plain loq@(Loqualization l) =
-               help @d (l10n_help_format_plain l) $
-               command "plain" $
-               runPermutation $
-               CommandSourceFormat_Plain
-                <<$?   option_help loq (help_usage $ command_source_plain loq)
-       command_source_html5 :: Loq d -> repr (Exit d) ArgCommand CommandSourceFormat
-       command_source_html5 loq@(Loqualization l) =
-               help @d (l10n_help_format_html5 l) $
-               command "html" $
-               runPermutation $
-               CommandSourceFormat_HTML5
-                <<$?   option_help loq (help_usage $ command_source_html5 loq)
-       
-       command_compile :: Loq d -> Lang -> repr (Exit d) ArgCommand CommandCompile
-       command_compile loq@(Loqualization l) lang =
-               help @d (l10n_help_command_compile l) $
-               command "compile" $
-               (setDefault <$$>) $
-               (runPermutation $
-                       CommandCompile
-                        <<$?   option_help loq (help_usage $ command_compile loq lang)
-                        <<|?>> option_output    loq
-                        <<|?>> option_lang      loq lang
-                        <<|?>> option_dump_tct  loq
-                        <<|?>> option_dump_xml  loq
-                        <<|?>> option_dump_deps loq)
-                <**> (command_compile_html5 loq
-                 <||> command_compile_xml   loq)
-                <**> string (l10n_var_file l)
-               where
-               setDefault a@CommandCompile{..}
-                | null compile_output = (a::CommandCompile){compile_output=compile_input-<.>fmt compile_format}
-                | otherwise = a
-               fmt = \case
-                CommandCompileFormat_XML{}   -> "xml"
-                CommandCompileFormat_HTML5{} -> "html"
-       command_compile_html5 :: Loq d -> repr (Exit d) ArgCommand CommandCompileFormat
-       command_compile_html5 loq@(Loqualization l) =
-               help @d (l10n_help_format_html5 l) $
-               command "html" $
-               runPermutation $
-                       CommandCompileFormat_HTML5
-                        <<$?   option_help loq (help_usage $ command_compile_html5 loq)
-                        <<|?>> option_html5_output_css
-                        <<|?>> option_html5_output_js
-                        <<|?>> option_dump_dtc loq
-               where
-               option_html5_output_css =
-                       (Nothing,) $
-                       (Just <$$>) $
-                       help @d (l10n_help_opt_output_css l) $
-                       opt (OptionNameLong "output-css") $
-                       string $ l10n_var_file l
-               option_html5_output_js =
-                       (Nothing,) $
-                       (Just <$$>) $
-                       help @d (l10n_help_opt_output_js l) $
-                       opt (OptionNameLong "output-js") $
-                       string $ l10n_var_file l
-       command_compile_xml :: Loq d -> repr (Exit d) ArgCommand CommandCompileFormat
-       command_compile_xml loq@(Loqualization l) =
-               help @d (l10n_help_format_xml l) $
-               command "xml" $
-               runPermutation $
-               CommandCompileFormat_XML
-                <<$?   option_help loq (help_usage $ command_compile_xml loq)
-       
-       command_schema :: Loq d -> repr (Exit d) ArgCommand CommandSchema
-       command_schema loq@(Loqualization l) =
-               help @d (l10n_help_command_schema l) $
-               command "schema" $
-               runPermutation $
-               CommandSchema
-                <<$? option_help loq (help_usage $ command_schema loq)
-instance Plain.Doc d => CLI d (Plain.Plain d)
-instance Plain.Doc d => CLI d Read.Parser
-instance Plain.Doc d => CLI d (Help.Help d)
-
-help_usage :: Plain.Doc d => Help.Help d (Exit d) t a -> d
-help_usage = Help.textHelp Help.defReader
- { Help.reader_command_indent = 2
- , Help.reader_option_indent  = 12
- }
-
--- * Type 'Lang'
--- | Supported locales
-type Langs = '[FR, EN]
-type Lang  = LocaleIn Langs
-
-getLang :: IO Lang
-getLang =
-       (\v -> Map.findWithDefault
-        (LocaleIn @Langs en_US)
-        (Text.pack $ List.takeWhile (\c -> Char.isAlphaNum c || c == '_') v)
-        (locales @Langs)) .
-       fromMaybe ""
-        <$> Env.lookupEnv "LANG"
-
--- ** Class 'L10n'
-type Loq d = Loqualization (L10n d)
--- | Localization
-class L10n_Var lang => L10n d lang where
-       l10n_cli                  :: FullLocale lang -> d
-       l10n_license              :: FullLocale lang -> d
-       l10n_help_version         :: FullLocale lang -> d
-       l10n_help_license         :: FullLocale lang -> d
-       l10n_help_command_source  :: FullLocale lang -> d
-       l10n_help_command_compile :: FullLocale lang -> d
-       l10n_help_command_schema  :: FullLocale lang -> d
-       l10n_help_opt_lang        :: FullLocale lang -> d
-       l10n_help_opt_output      :: FullLocale lang -> d
-       l10n_help_opt_output_css  :: FullLocale lang -> d
-       l10n_help_opt_output_js   :: FullLocale lang -> d
-       l10n_help_opt_dump_tct    :: FullLocale lang -> d
-       l10n_help_opt_dump_xml    :: FullLocale lang -> d
-       l10n_help_opt_dump_deps   :: FullLocale lang -> d
-       l10n_help_opt_dump_dtc    :: FullLocale lang -> d
-       l10n_help_format          :: FullLocale lang -> d
-       l10n_help_format_plain    :: FullLocale lang -> d
-       l10n_help_format_html5    :: FullLocale lang -> d
-       l10n_help_format_xml      :: FullLocale lang -> d
-       l10n_help_opt_input       :: FullLocale lang -> d
-       l10n_help_opt_help        :: FullLocale lang -> d
-class L10n_Var lang where
-       l10n_var_file   :: FullLocale lang -> Name
-       l10n_var_locale :: FullLocale lang -> Name
-
--- * Type 'Doc'
-data Doc d
- =   Doc d
- |   Var Name
- deriving Show
-instance (Semigroup d, IsString d) => Semigroup (Doc d) where
-       Doc x <> Doc y = Doc (x<>y)
-       x <> y = Doc $ runDoc x <> runDoc y
-instance (Semigroup d, Monoid d, IsString d) => Monoid (Doc d) where
-       mempty  = Doc mempty
-       mappend = (<>)
-instance Doc.Breakable d => IsString (Doc d) where
-       fromString = Doc . Plain.words
-instance (IsString d, Semigroup d, Monoid d) => IsList (Doc d) where
-       type Item (Doc d) = Doc d
-       toList = pure
-       fromList = Doc . foldMap runDoc
-instance (IsString d, Semigroup d) => Doc.Trans (Doc d) where
-       type ReprOf (Doc d) = d
-       trans   = Doc
-       unTrans = runDoc
-instance Doc.Breakable d => Doc.Textable (Doc d)
-instance (Doc.Breakable d, Doc.Indentable d) => Doc.Indentable (Doc d)
-instance Doc.Breakable d => Doc.Breakable (Doc d)
-instance (IsString d, Semigroup d, Doc.Decorable d) => Doc.Decorable (Doc d)
-instance (IsString d, Semigroup d, Doc.Colorable d) => Doc.Colorable (Doc d)
-instance Plain.Doc d => Plain.Doc (Doc d)
-
-runDoc :: (IsString d, Semigroup d) => Doc d -> d
-runDoc = \case
- Doc d -> d
- Var n -> "<"<>fromString n<>">"
-
-instance (IsString d, Semigroup d, Monoid d, Doc.Breakable d) => L10n (Doc d) EN where
-       l10n_cli _ = "Compiler of Convivial Technical Document (DTC)."
-       l10n_license _ =
-               fromString $
-               List.intercalate "\n"
-                [ "License: GNU GPLv3+"
-                , "Copyright: Julien Moutinho <julm+hdoc@autogeree.net>"
-                , ""
-                , "hdoc is free software: you can redistribute it and/or modify it"
-                , "under the terms of the GNU General Public License (GPL)"
-                , "as published by the Free Software Foundation;"
-                , "either in version 3, or (at your option) any later version."
-                , ""
-                , "hdoc is distributed in the hope that it will be useful,"
-                , "but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY"
-                , "or FITNESS FOR A PARTICULAR PURPOSE."
-                , ""
-                , "See the GNU GPL for more details."
-                , "You should have received a copy of the GNU GPL along with hdoc."
-                , "If not, see: http://www.gnu.org/licenses/"
-                ]
-       l10n_help_version         _ = "Show the version of this program."
-       l10n_help_license         _ = "Inform about the license of this program."
-       l10n_help_command_source  _ = "Format the source code of a TCT document."
-       l10n_help_command_compile _ = "Compile a TCT document into a format optimized for reading."
-       l10n_help_command_schema  _ = "Show in RNC (RelaxNG Compact) format the XML schema of the DTC format."
-       l10n_help_opt_lang        l = ["Use the language given by ", Var $ l10n_var_locale l, "."]
-       l10n_help_opt_output      l = ["Output document into ", Var $ l10n_var_file l]
-       l10n_help_opt_output_css  l = [ "Output CSS stylesheet into "
-                                     , Var $ l10n_var_file l
-                                     , " (if any), instead of incorporating it into the HTML."
-                                     ]
-       l10n_help_opt_output_js   l = [ "Output JavaScript script into "
-                                     , Var $ l10n_var_file l
-                                     , " (if any), instead of incorporating it into the HTML."
-                                     ]
-       l10n_help_opt_dump_tct    l = [ "Dump internal TCT representation of "
-                                     , Var $ l10n_var_file l,".tct file,"
-                                     , " in a"
-                                     , Var $ l10n_var_file l,".tct.dump file."
-                                     ]
-       l10n_help_opt_dump_xml    l = [ "Dump internal XML representation of "
-                                     , Var $ l10n_var_file l,".tct file,"
-                                     , " in a"
-                                     , Var $ l10n_var_file l,".xml.dump file."
-                                     ]
-       l10n_help_opt_dump_deps   l = [ "Dump dependencies of ", Var $ l10n_var_file l,".tct file"
-                                     , " in ", Var $ l10n_var_file l,".deps file,"
-                                     , " separated by newlines."
-                                     ]
-       l10n_help_opt_dump_dtc    _ = "Dump internal representation of DTC."
-       l10n_help_opt_help        _ = "Show this help."
-       l10n_help_format          _ = "Output format."
-       l10n_help_format_plain    _ = "Output as plain text."
-       l10n_help_format_html5    _ = "Output as HTML5."
-       l10n_help_format_xml      _ = "Output as XML."
-       l10n_help_opt_input       l = ["Read input from ", Var $ l10n_var_file l, "."]
-instance (IsString d , Semigroup d, Monoid d, Doc.Breakable d) => L10n (Doc d) FR where
-       l10n_cli _ = "Compilateur de Document Technique Convivial (DTC)."
-       l10n_license _ =
-               fromString $
-               List.intercalate "\n"
-                [ "Licence : GPLv3+ GNU"
-                , "Droit d’auteur : Julien Moutinho <julm+hdoc@autogeree.net>"
-                , ""
-                , "hdoc est un logiciel libre : vous pouvez le redistribuer et/ou le modifier"
-                , "selon les termes de la Licence Publique Générale (GPL) GNU"
-                , "telle que publiée par la Free Software Foundation ;"
-                , "en version 3, ou (à votre choix) n’importe quelle version ultérieure."
-                , ""
-                , "hdoc est distribué dans l’espoir qu’il sera utile,"
-                , "mais SANS AUCUNE GARANTIE ; sans même la garantie implicite de COMMERCIALISATION"
-                , "ou de CONVENANCE À UN BUT PARTICULIER."
-                , ""
-                , "Voyez la GPL pour davantage de détails."
-                , "Vous devriez avoir reçu une copie de la GPL avec hdoc."
-                , "Si non, voyez : http://www.gnu.org/licenses/"
-                ]
-       l10n_help_version         _ = "Affiche la version de ce logiciel."
-       l10n_help_license         _ = "Informe sur la licence de ce logiciel."
-       l10n_help_command_source  _ = "Lit un document TCT et écrit un rendu préservant sa syntaxe."
-       l10n_help_command_compile _ = "Compile un document TCT vers un format optimisé pour la lecture."
-       l10n_help_command_schema  _ = "Affiche au format RNC (RelaxNG Compact) le schéma XML du format DTC."
-       l10n_help_opt_lang        l = ["Utilise le langage indiqué par ", Var $ l10n_var_locale l, "."]
-       l10n_help_opt_output      l = ["Écrit dans ", Var $ l10n_var_file l, "."]
-       l10n_help_opt_output_css  l = [ "Écrit la feuille de style CSS dans "
-                                     , Var $ l10n_var_file l
-                                     , ", au lieu de l’incorporer dans le HTML."
-                                     ]
-       l10n_help_opt_output_js   l = [ "Écrit le script JavaScript dans "
-                                     , Var $ l10n_var_file l
-                                     , ", au lieu de l’incorporer dans le HTML."
-                                     ]
-       l10n_help_opt_dump_tct    l = [ "Écrit la représentation TCT interne de "
-                                     , Var $ l10n_var_file l,".tct,"
-                                     , " dans "
-                                     , Var $ l10n_var_file l,".tct.dump."
-                                     ]
-       l10n_help_opt_dump_xml    l = [ "Écrit la représentation XML interne de "
-                                     , Var $ l10n_var_file l,".tct,"
-                                     , " dans "
-                                     , Var $ l10n_var_file l,".xml.dump."
-                                     ]
-       l10n_help_opt_dump_deps   l = [ "Écrit les dépendences de ", Var $ l10n_var_file l,".tct"
-                                     , " dans ", Var $ l10n_var_file l,".deps,"
-                                     , " séparées par des retours à la ligne."
-                                     ]
-       l10n_help_opt_dump_dtc    _ = "Écrit la représentation interne du DTC."
-       l10n_help_opt_help        _ = "Affiche cette aide."
-       l10n_help_format          _ = "Format de sortie."
-       l10n_help_format_plain    _ = "Produit du texte brut."
-       l10n_help_format_html5    _ = "Produit du HTML5."
-       l10n_help_format_xml      _ = "Produit du XML."
-       l10n_help_opt_input       l = ["Lit depuis ", Var $ l10n_var_file l, "."]
-instance L10n_Var EN where
-       l10n_var_file   _ = "file"
-       l10n_var_locale _ = "locale"
-instance L10n_Var FR where
-       l10n_var_file   _ = "fichier"
-       l10n_var_locale _ = "locale"
similarity index 100%
rename from Control/HLint.hs
rename to src/Control/HLint.hs
similarity index 99%
rename from Control/Monad/Utils.hs
rename to src/Control/Monad/Utils.hs
index e40575dc4ba6e86452b8cb0db1d883908e6d8820..f2a0d3c999bd872218cdad916efa485756607fc0 100644 (file)
@@ -1,3 +1,4 @@
+{-# LANGUAGE BangPatterns #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 module Control.Monad.Utils where
similarity index 99%
rename from Text/Blaze/DTC.hs
rename to src/Text/Blaze/DTC.hs
index 92c7f64bbe1ac7cb7ba975dbc8b6e84c403dda6f..52a21f8d10b5689784692900f379e6b76dbcb8ec 100644 (file)
@@ -13,7 +13,7 @@ import qualified Data.Text.Lazy as TL
 import Text.Blaze.Utils
 import Text.Blaze.XML (XML)
 
-import Hdoc.DTC.Document
+import Textphile.DTC.Document
 
 -- * Type 'DTC'
 type DTC = XML
similarity index 100%
rename from Hdoc/DTC/HLint.hs
rename to src/Text/Blaze/HLint.hs
similarity index 100%
rename from Text/Blaze/HTML5.hs
rename to src/Text/Blaze/HTML5.hs
similarity index 100%
rename from Text/Blaze/Utils.hs
rename to src/Text/Blaze/Utils.hs
similarity index 93%
rename from Text/Blaze/XML.hs
rename to src/Text/Blaze/XML.hs
index 08650ebfc6d71204888fae1ab529bfde1560abe0..f4288cae55dab8a028a7661dc43b15d2d747e899 100644 (file)
@@ -2,14 +2,14 @@
 module Text.Blaze.XML where
 
 import Data.Function ((.))
-import Hdoc.XML
+import Textphile.XML
 import Prelude (Double)
 import Text.Blaze
 import Text.Blaze.Utils
 import Text.Show (Show(..))
 import qualified Symantic.XML as XML
 
-import Hdoc.Utils (Nat(..), Nat1(..))
+import Textphile.Utils (Nat(..), Nat1(..))
 
 -- * Type 'XML'
 type XML = Markup
similarity index 100%
rename from Hdoc/DTC/Read/HLint.hs
rename to src/Text/HLint.hs
similarity index 97%
rename from Hdoc/DTC/Analyze/Check.hs
rename to src/Textphile/DTC/Analyze/Check.hs
index 1a344ab6284da5d73d0d0c28cd21c6dfaedd5019..58393ce9fae0599f8e41690437a9d1d85947db5e 100644 (file)
@@ -1,5 +1,5 @@
 {-# LANGUAGE FlexibleInstances #-}
-module Hdoc.DTC.Analyze.Check where
+module Textphile.DTC.Analyze.Check where
 
 import Control.Arrow ((&&&))
 import Data.Default.Class (Default(..))
@@ -15,8 +15,8 @@ import Data.Tuple (fst)
 import Text.Show (Show(..))
 import qualified Data.HashMap.Strict as HM
 
-import Hdoc.DTC.Document
-import Hdoc.DTC.Analyze.Collect
+import Textphile.DTC.Document
+import Textphile.DTC.Analyze.Collect
 
 -- ** Type 'Errors'
 data Errors a = Errors
similarity index 98%
rename from Hdoc/DTC/Analyze/Collect.hs
rename to src/Textphile/DTC/Analyze/Collect.hs
index 76515b693db270d1f1f501c2e6b1ad0e064f37fe..020d47956d9bfa2c028f403ba2c1588a618c21f7 100644 (file)
@@ -1,6 +1,6 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverloadedStrings #-}
-module Hdoc.DTC.Analyze.Collect where
+module Textphile.DTC.Analyze.Collect where
 
 import Control.Applicative (Applicative(..), liftA2)
 import Control.Monad
@@ -24,9 +24,9 @@ import qualified Data.Text.Lazy as TL
 import qualified Data.TreeSeq.Strict as TS
 import qualified Data.TreeMap.Strict as TM
 
-import qualified Hdoc.TCT.Cell as TCT
-import Hdoc.DTC.Document as DTC
-import qualified Hdoc.XML as XML
+import qualified Textphile.TCT.Cell as TCT
+import Textphile.DTC.Document as DTC
+import qualified Textphile.XML as XML
 
 -- * Type 'Reader'
 newtype Reader = Reader
similarity index 98%
rename from Hdoc/DTC/Analyze/Index.hs
rename to src/Textphile/DTC/Analyze/Index.hs
index bf07ab6d49f288a2a5601a5e0a7c2aa6b9ecfb66..f316015e9b87878cfdf79b5656aa42fac7e84ed5 100644 (file)
@@ -1,6 +1,6 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverloadedStrings #-}
-module Hdoc.DTC.Analyze.Index where
+module Textphile.DTC.Analyze.Index where
 
 import Control.Applicative (Applicative(..))
 import Control.Monad (Monad(..))
@@ -32,8 +32,8 @@ import qualified Data.Text.Lazy as TL
 import qualified Data.TreeMap.Strict as TM
 import qualified Data.TreeSeq.Strict as TS
 
-import Hdoc.DTC.Document as DTC
-import qualified Hdoc.XML as XML
+import Textphile.DTC.Document as DTC
+import qualified Textphile.XML as XML
 
 {-
 -- * Type 'Index'
similarity index 98%
rename from Hdoc/DTC/Document.hs
rename to src/Textphile/DTC/Document.hs
index 8e22e3338c3af5eeb5168f308113318d8fba1062..52f1c8184f8d0c6c02925d87f161cc2ea3ae51f7 100644 (file)
@@ -4,8 +4,8 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# LANGUAGE OverloadedStrings #-}
-module Hdoc.DTC.Document
- ( module Hdoc.DTC.Document
+module Textphile.DTC.Document
+ ( module Textphile.DTC.Document
  , Ident(..), URL(..), Nat(..), Nat1(..)
  , succNat, succNat1
  , FilePath
@@ -38,10 +38,10 @@ import qualified Data.TreeMap.Strict as TM
 import qualified Data.TreeSeq.Strict as TS
 import qualified Majority.Judgment as MJ
 
-import Hdoc.Utils (Nat(..), Nat1(..), succNat, succNat1)
-import Hdoc.XML (Ident(..), URL(..))
-import qualified Hdoc.XML as XML
-import qualified Hdoc.TCT.Cell as TCT
+import Textphile.Utils (Nat(..), Nat1(..), succNat, succNat1)
+import Textphile.XML (Ident(..), URL(..))
+import qualified Textphile.XML as XML
+import qualified Textphile.TCT.Cell as TCT
 
 -- * Type 'Document'
 data Document = Document
similarity index 100%
rename from Hdoc/HLint.hs
rename to src/Textphile/DTC/HLint.hs
similarity index 97%
rename from Hdoc/DTC/Read/TCT.hs
rename to src/Textphile/DTC/Read/TCT.hs
index dcee202fcd4cc315123a5f665749cdaf9481d417..5e97189ff3a8847867309aad759f4982d20dd5da 100644 (file)
@@ -6,7 +6,7 @@
 {-# LANGUAGE ViewPatterns #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 -- | Read DTC from TCT.
-module Hdoc.DTC.Read.TCT where
+module Textphile.DTC.Read.TCT where
 import Control.Applicative (Applicative(..), optional)
 import Control.Monad (Monad(..))
 import Data.Bool
@@ -45,14 +45,14 @@ import qualified Symantic.XML as XML
 import qualified Text.Megaparsec as P
 import qualified Text.Read as Read
 
-import Hdoc.TCT hiding (Parser, ErrorRead)
-import Hdoc.XML (XML, XMLs)
-import Hdoc.Utils (Nat(..), Nat1(..), succNat1)
-import qualified Hdoc.DTC.Document as DTC
-import qualified Hdoc.DTC.Sym as DTC
-import qualified Hdoc.RNC as RNC
-import qualified Hdoc.XML as XML
-import qualified Hdoc.TCT.Cell as TCT
+import Textphile.TCT hiding (Parser, ErrorRead)
+import Textphile.XML (XML, XMLs)
+import Textphile.Utils (Nat(..), Nat1(..), succNat1)
+import qualified Textphile.DTC.Document as DTC
+import qualified Textphile.DTC.Sym as DTC
+import qualified Textphile.RNC as RNC
+import qualified Textphile.XML as XML
+import qualified Textphile.TCT.Cell as TCT
 
 readDTC ::
  DTC.Sym_DTC Parser =>
similarity index 98%
rename from Hdoc/DTC/Sym.hs
rename to src/Textphile/DTC/Sym.hs
index f987f90a2ab82b441b5f4735cb0726291681f76b..3ddb60b1904ca297383363b92b2d419307ceef23 100644 (file)
@@ -2,7 +2,7 @@
 {-# LANGUAGE NoMonomorphismRestriction #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE RankNTypes #-}
-module Hdoc.DTC.Sym where
+module Textphile.DTC.Sym where
 
 import Control.Applicative (Applicative(..), (<$>), (<$))
 import Control.Arrow (second)
@@ -22,12 +22,12 @@ import qualified Data.Text.Lazy as TL
 import qualified Symantic.RNC as RNC
 import qualified Symantic.XML as XML
 
-import Hdoc.RNC as RNC
-import Hdoc.XML
-import qualified Hdoc.DTC.Analyze.Index as Index
-import qualified Hdoc.DTC.Document as DTC
-import qualified Hdoc.TCT.Cell as TCT
-import qualified Hdoc.XML as XML
+import Textphile.RNC as RNC
+import Textphile.XML
+import qualified Textphile.DTC.Analyze.Index as Index
+import qualified Textphile.DTC.Document as DTC
+import qualified Textphile.TCT.Cell as TCT
+import qualified Textphile.XML as XML
 
 element :: RNC.Sym_RNC repr => XML.NCName -> repr a -> repr a
 element = RNC.element . XML.QName xmlns_dtc
similarity index 96%
rename from Hdoc/DTC/Write/HTML5.hs
rename to src/Textphile/DTC/Write/HTML5.hs
index db33f55d2f03259fc1c305f950187da5b0a3f993..98fca3fd497cdc17ce1638c86e643bd34d7b2343 100644 (file)
@@ -7,12 +7,12 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.DTC.Write.HTML5
- ( module Hdoc.DTC.Write.HTML5
- , module Hdoc.DTC.Write.HTML5.Ident
- , module Hdoc.DTC.Write.HTML5.Base
- , module Hdoc.DTC.Write.HTML5.Judgment
- -- , module Hdoc.DTC.Write.HTML5.Error
+module Textphile.DTC.Write.HTML5
+ ( module Textphile.DTC.Write.HTML5
+ , module Textphile.DTC.Write.HTML5.Ident
+ , module Textphile.DTC.Write.HTML5.Base
+ , module Textphile.DTC.Write.HTML5.Judgment
+ -- , module Textphile.DTC.Write.HTML5.Error
  ) where
 
 import Control.Applicative (Applicative(..))
@@ -58,24 +58,24 @@ import qualified Text.Blaze.Html5.Attributes  as HA
 import qualified Text.Blaze.Internal as H
 
 import Control.Monad.Utils
-import Hdoc.DTC.Document as DTC
-import Hdoc.DTC.Write.HTML5.Base
-import Hdoc.DTC.Write.HTML5.Error ()
-import Hdoc.DTC.Write.HTML5.Ident
-import Hdoc.DTC.Write.HTML5.Judgment
-import Hdoc.DTC.Write.Plain (Plainify(..))
-import Hdoc.DTC.Write.XML ()
-import Hdoc.Utils
+import Textphile.DTC.Document as DTC
+import Textphile.DTC.Write.HTML5.Base
+import Textphile.DTC.Write.HTML5.Error ()
+import Textphile.DTC.Write.HTML5.Ident
+import Textphile.DTC.Write.HTML5.Judgment
+import Textphile.DTC.Write.Plain (Plainify(..))
+import Textphile.DTC.Write.XML ()
+import Textphile.Utils
 import Text.Blaze.Utils
 import Text.Blaze.XML ()
-import qualified Hdoc.DTC.Analyze.Check as Analyze
-import qualified Hdoc.DTC.Analyze.Collect as Analyze
-import qualified Hdoc.DTC.Analyze.Index as Analyze
-import qualified Hdoc.DTC.Write.Plain as Plain
-import qualified Hdoc.TCT.Cell as TCT
-import qualified Hdoc.Utils as FS
-import qualified Hdoc.XML as XML
-import qualified Paths_hdoc as Hdoc
+import qualified Textphile.DTC.Analyze.Check as Analyze
+import qualified Textphile.DTC.Analyze.Collect as Analyze
+import qualified Textphile.DTC.Analyze.Index as Analyze
+import qualified Textphile.DTC.Write.Plain as Plain
+import qualified Textphile.TCT.Cell as TCT
+import qualified Textphile.Utils as FS
+import qualified Textphile.XML as XML
+import qualified Paths_hdoc as Textphile
 import Debug.Trace
 
 debug :: Show a => String -> a -> a
@@ -132,7 +132,7 @@ writeHTML5Head Config{..} Reader{..} Writer{..} Document{..} = do
                -- unless (any (\DTC.Link{..} -> link_rel == "stylesheet" && link_url /= URL "") links) $ do
                (`foldMap` writer_styles) $ \case
                 Left css -> do
-                       content <- FS.readFile =<< Hdoc.getDataFileName ("style"</>css)
+                       content <- FS.readFile =<< Textphile.getDataFileName ("style"</>css)
                        return $ H.style ! HA.type_ "text/css" $
                                H.toMarkup content
                 Right content -> return $ do
@@ -142,7 +142,7 @@ writeHTML5Head Config{..} Reader{..} Writer{..} Document{..} = do
                                H.toMarkup content
        scripts :: Html <-
                (`foldMap` writer_scripts) $ \script -> do
-                       content <- FS.readFile =<< Hdoc.getDataFileName ("style"</>script)
+                       content <- FS.readFile =<< Textphile.getDataFileName ("style"</>script)
                        return $ H.script ! HA.type_ "application/javascript" $
                                H.toMarkup content
                {-
similarity index 95%
rename from Hdoc/DTC/Write/HTML5/Base.hs
rename to src/Textphile/DTC/Write/HTML5/Base.hs
index 331770a97c47cf37499b5f960a4b91fca9bd86a0..2d56dec288be62fb1a57c278fb02c00f936e64c4 100644 (file)
@@ -8,7 +8,7 @@
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeApplications #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.DTC.Write.HTML5.Base where
+module Textphile.DTC.Write.HTML5.Base where
 
 import Control.Monad (Monad(..))
 import Data.Bool
@@ -39,13 +39,13 @@ import qualified Text.Blaze.Html5 as H
 import qualified Text.Blaze.Internal as H
 
 import Control.Monad.Utils
-import Hdoc.Utils ()
-import Hdoc.DTC.Document as DTC
-import Hdoc.DTC.Write.XML ()
-import qualified Hdoc.DTC.Analyze.Check   as Analyze
-import qualified Hdoc.DTC.Analyze.Collect as Analyze
--- import qualified Hdoc.DTC.Analyze.Index   as Analyze
-import qualified Hdoc.DTC.Write.Plain as Plain
+import Textphile.Utils ()
+import Textphile.DTC.Document as DTC
+import Textphile.DTC.Write.XML ()
+import qualified Textphile.DTC.Analyze.Check   as Analyze
+import qualified Textphile.DTC.Analyze.Collect as Analyze
+-- import qualified Textphile.DTC.Analyze.Index   as Analyze
+import qualified Textphile.DTC.Write.Plain as Plain
 import qualified Text.Blaze.Internal as B
 
 -- * Type 'HTML5'
@@ -71,7 +71,7 @@ instance Default Config where
         { config_css       = Right "style/dtc-html5.css"
         , config_js        = Right "" -- "style/dtc-html5.js"
         , config_locale    = LocaleIn @'[EN] en_US
-        , config_generator = "https://hackage.haskell.org/package/hdoc"
+        , config_generator = "https://hackage.haskell.org/package/textphile"
         }
 
 -- ** Type 'Reader'
similarity index 94%
rename from Hdoc/DTC/Write/HTML5/Error.hs
rename to src/Textphile/DTC/Write/HTML5/Error.hs
index 80a1e32530ee034df7e32a6d9f86d680054f889f..034778a7a5bafbe83998d1254c91829f20239642 100644 (file)
@@ -4,7 +4,7 @@
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.DTC.Write.HTML5.Error where
+module Textphile.DTC.Write.HTML5.Error where
 
 import Control.Applicative (Applicative(..))
 import Control.Monad (forM_, mapM_)
@@ -34,16 +34,16 @@ import qualified Text.Blaze.Html5 as H
 import qualified Text.Blaze.Html5.Attributes  as HA
 
 import Control.Monad.Utils
-import Hdoc.DTC.Document as DTC
-import Hdoc.DTC.Write.HTML5.Base
-import Hdoc.DTC.Write.HTML5.Ident
-import Hdoc.DTC.Write.XML ()
+import Textphile.DTC.Document as DTC
+import Textphile.DTC.Write.HTML5.Base
+import Textphile.DTC.Write.HTML5.Ident
+import Textphile.DTC.Write.XML ()
 import Text.Blaze.Utils
-import qualified Hdoc.DTC.Analyze.Check as Analyze
-import qualified Hdoc.DTC.Analyze.Collect as Analyze
-import qualified Hdoc.DTC.Write.Plain as Plain
-import qualified Hdoc.TCT.Cell as TCT
-import qualified Hdoc.XML as XML
+import qualified Textphile.DTC.Analyze.Check as Analyze
+import qualified Textphile.DTC.Analyze.Collect as Analyze
+import qualified Textphile.DTC.Write.Plain as Plain
+import qualified Textphile.TCT.Cell as TCT
+import qualified Textphile.XML as XML
 
 instance (Html5ify Plain, Html5ify TCT.Location) => Html5ify (Analyze.Errors (Seq Location)) where
        html5ify Analyze.Errors{..} = do
similarity index 94%
rename from Hdoc/DTC/Write/HTML5/Ident.hs
rename to src/Textphile/DTC/Write/HTML5/Ident.hs
index 2218f599ac8420cbe610012e336a583e8bde55d3..5e18237d197d385dad7be25ce1cc6942fefc0aaa 100644 (file)
@@ -1,6 +1,6 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverloadedStrings #-}
-module Hdoc.DTC.Write.HTML5.Ident where
+module Textphile.DTC.Write.HTML5.Ident where
 
 import Control.Category as Cat
 import Control.Monad (Monad(..))
@@ -30,11 +30,11 @@ import qualified Symantic.XML as XML
 
 import Text.Blaze.Utils
 
-import Hdoc.Utils ()
-import Hdoc.DTC.Document as DTC
-import Hdoc.DTC.Analyze.Index (plainifyWords)
-import qualified Hdoc.DTC.Write.Plain as Plain
-import qualified Hdoc.XML as XML
+import Textphile.Utils ()
+import Textphile.DTC.Document as DTC
+import Textphile.DTC.Analyze.Index (plainifyWords)
+import qualified Textphile.DTC.Write.Plain as Plain
+import qualified Textphile.XML as XML
 
 -- * Class 'Identify'
 class Identify a where
similarity index 97%
rename from Hdoc/DTC/Write/HTML5/Judgment.hs
rename to src/Textphile/DTC/Write/HTML5/Judgment.hs
index c11c8c789e795f6a4077a5b16ab9e7c57d04c5d0..217512b197cc62e7efe147970077ddb0f7e7b707 100644 (file)
@@ -4,7 +4,7 @@
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.DTC.Write.HTML5.Judgment where
+module Textphile.DTC.Write.HTML5.Judgment where
 
 import Control.Arrow ((&&&))
 import Control.Monad (Monad(..), (=<<), forM, forM_, join)
@@ -44,18 +44,18 @@ import qualified Prelude (error)
 import qualified Text.Blaze.Html5 as H
 import qualified Text.Blaze.Html5.Attributes  as HA
 
-import Hdoc.DTC.Document as DTC
-import Hdoc.DTC.Write.HTML5.Base
-import Hdoc.DTC.Write.HTML5.Ident
-import Hdoc.DTC.Write.XML ()
+import Textphile.DTC.Document as DTC
+import Textphile.DTC.Write.HTML5.Base
+import Textphile.DTC.Write.HTML5.Ident
+import Textphile.DTC.Write.XML ()
 import Control.Monad.Utils
 import Text.Blaze.Utils
-import qualified Hdoc.XML as XML
-import qualified Hdoc.DTC.Analyze.Collect as Analyze
-import qualified Hdoc.DTC.Analyze.Check as Analyze
-import qualified Hdoc.DTC.Write.Plain as Plain
+import qualified Textphile.XML as XML
+import qualified Textphile.DTC.Analyze.Collect as Analyze
+import qualified Textphile.DTC.Analyze.Check as Analyze
+import qualified Textphile.DTC.Write.Plain as Plain
 
--- import qualified Hdoc.TCT.Debug as Debug
+-- import qualified Textphile.TCT.Debug as Debug
 
 -- <debug>
 -- import Debug.Trace
similarity index 97%
rename from Hdoc/DTC/Write/Plain.hs
rename to src/Textphile/DTC/Write/Plain.hs
index 6e6efd8c3fce1e900f9b53b0e0a95743c5f513f9..8ea52903f9e6273d8e1fccb3cf16acbddf03fcd3 100644 (file)
@@ -6,7 +6,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.DTC.Write.Plain where
+module Textphile.DTC.Write.Plain where
 
 import Control.Applicative (Applicative(..), liftA2)
 import Control.Category
@@ -31,9 +31,9 @@ import qualified Symantic.XML as XML
 
 import Data.Locale hiding (Index)
 
-import Hdoc.DTC.Write.XML ()
-import Hdoc.DTC.Document as DTC hiding (Plain)
-import qualified Hdoc.DTC.Document as DTC
+import Textphile.DTC.Write.XML ()
+import Textphile.DTC.Document as DTC hiding (Plain)
+import qualified Textphile.DTC.Document as DTC
 
 -- * Type 'Plain'
 type Plain = R.Reader Reader TLB.Builder
similarity index 98%
rename from Hdoc/DTC/Write/XML.hs
rename to src/Textphile/DTC/Write/XML.hs
index e26e78e2823c1a48d22927afed128d99fe436403..4aa0aa9cef7db3aba735aa32e948ac788d35ef99 100644 (file)
@@ -1,7 +1,7 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.DTC.Write.XML where
+module Textphile.DTC.Write.XML where
 
 import Control.Monad (forM_)
 import Data.Bool
@@ -23,8 +23,8 @@ import qualified Text.Blaze.DTC.Attributes as XA
 import qualified Text.Blaze.Internal as B
 
 import Data.Locale
-import Hdoc.DTC.Analyze.Index (plainifyWords)
-import Hdoc.DTC.Document as DTC
+import Textphile.DTC.Analyze.Index (plainifyWords)
+import Textphile.DTC.Document as DTC
 
 writeXML :: Locales ls => LocaleIn ls -> Document -> XML
 writeXML _loc Document{..} = do
similarity index 90%
rename from Hdoc/RNC.hs
rename to src/Textphile/RNC.hs
index 235e49f32593af465a7d8a6f6bd78f6801dc7770..4f197bd63e79f23a48b493f943cfcd89c078a00f 100644 (file)
@@ -1,14 +1,14 @@
 {-# LANGUAGE OverloadedStrings #-}
-module Hdoc.RNC where
+module Textphile.RNC where
 import Data.Bool (Bool)
 import Data.Int (Int)
 import Data.Monoid (Monoid(..))
 import Data.Ratio (Rational)
 import qualified Data.Text.Lazy as TL
 import qualified Symantic.RNC as RNC
-import qualified Symantic.RNC.Write as RNC
+-- import qualified Symantic.RNC.Write as RNC
 
-import Hdoc.Utils (Nat, Nat1)
+import Textphile.Utils (Nat, Nat1)
 
 -- * Class 'Sym_RNC_Extra'
 class RNC.Sym_RNC repr => Sym_RNC_Extra repr where
diff --git a/src/Textphile/TCT.hs b/src/Textphile/TCT.hs
new file mode 100644 (file)
index 0000000..cedba90
--- /dev/null
@@ -0,0 +1,11 @@
+module Textphile.TCT
+ ( module Textphile.TCT.Cell
+ , module Textphile.TCT.Tree
+ , module Textphile.TCT.Elem
+ , module Textphile.TCT.Read
+ ) where
+
+import Textphile.TCT.Cell
+import Textphile.TCT.Tree
+import Textphile.TCT.Elem
+import Textphile.TCT.Read
similarity index 97%
rename from Hdoc/TCT/Cell.hs
rename to src/Textphile/TCT/Cell.hs
index 72aa7679d2f17a9f1127a2b9d2d40b0798ff1458..43609f38f882b03bb8709b715bd21a1cc31dd87c 100644 (file)
@@ -1,7 +1,7 @@
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverloadedStrings #-}
-module Hdoc.TCT.Cell
- ( module Hdoc.TCT.Cell
+module Textphile.TCT.Cell
+ ( module Textphile.TCT.Cell
  , XML.FileRange(..)
  , XML.NoSource(..)
  , XML.Sourced(..)
@@ -23,7 +23,7 @@ import qualified Data.Text.Lazy as TL
 import qualified Symantic.XML as XML
 import qualified Text.Megaparsec as P
 
-import Hdoc.TCT.Debug
+import Textphile.TCT.Debug
 
 {-
 -- * Type 'Pos'
similarity index 99%
rename from Hdoc/TCT/Debug.hs
rename to src/Textphile/TCT/Debug.hs
index 752d3daaa99babad9e224debd86ded6cb825b756..ef043cf7827539e8f2c339ce9af819f5dac12fcf 100644 (file)
@@ -5,7 +5,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE Rank2Types #-}
 {-# LANGUAGE TypeFamilies #-}
-module Hdoc.TCT.Debug where
+module Textphile.TCT.Debug where
 
 import Control.Monad (Monad(..), mapM)
 import Data.Bool
similarity index 94%
rename from Hdoc/TCT/Elem.hs
rename to src/Textphile/TCT/Elem.hs
index ec07cdad34a608317d221f5ed976e3627d687527..d980f94c7252285c7e2d00a7ba6776ba1a914f97 100644 (file)
@@ -1,4 +1,4 @@
-module Hdoc.TCT.Elem where
+module Textphile.TCT.Elem where
 
 import Data.Eq (Eq)
 import Data.Ord (Ord)
similarity index 93%
rename from Hdoc/TCT/Read.hs
rename to src/Textphile/TCT/Read.hs
index 963d793112e3fafc0b3aaeb6c46e839dd387625b..259c26f9787d590ad2fbbfacc38b1ec4fe8308f9 100644 (file)
@@ -1,9 +1,9 @@
-module Hdoc.TCT.Read
- ( module Hdoc.TCT.Read.Cell
- , module Hdoc.TCT.Read.Elem
- , module Hdoc.TCT.Read.Token
- , module Hdoc.TCT.Read.Tree
- , module Hdoc.TCT.Read
+module Textphile.TCT.Read
+ ( module Textphile.TCT.Read.Cell
+ , module Textphile.TCT.Read.Elem
+ , module Textphile.TCT.Read.Token
+ , module Textphile.TCT.Read.Tree
+ , module Textphile.TCT.Read
  ) where
 
 import Control.Applicative (Applicative(..))
@@ -33,13 +33,13 @@ import qualified System.FilePath as FilePath
 import qualified System.IO.Error as IO
 import qualified Text.Megaparsec as P
 
-import Hdoc.TCT.Debug
-import Hdoc.TCT.Tree
-import Hdoc.TCT.Cell
-import Hdoc.TCT.Read.Cell
-import Hdoc.TCT.Read.Elem
-import Hdoc.TCT.Read.Tree
-import Hdoc.TCT.Read.Token
+import Textphile.TCT.Debug
+import Textphile.TCT.Tree
+import Textphile.TCT.Cell
+import Textphile.TCT.Read.Cell
+import Textphile.TCT.Read.Elem
+import Textphile.TCT.Read.Tree
+import Textphile.TCT.Read.Token
 
 -- | Parsing is done in two phases:
 --
similarity index 98%
rename from Hdoc/TCT/Read/Cell.hs
rename to src/Textphile/TCT/Read/Cell.hs
index 36ded353ce7957fd01a77e306d4dfd7efeedb399..d99fbc542fa00c8221a4078f1138637de64a22df 100644 (file)
@@ -3,7 +3,7 @@
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE Rank2Types #-}
 {-# LANGUAGE TypeFamilies #-}
-module Hdoc.TCT.Read.Cell where
+module Textphile.TCT.Read.Cell where
 
 import Control.Applicative (Applicative(..))
 import Control.Monad (Monad(..))
@@ -28,7 +28,7 @@ import qualified Data.Set as Set
 import qualified Data.Text.Lazy as TL
 import qualified Text.Megaparsec as P
 
-import Hdoc.TCT.Cell
+import Textphile.TCT.Cell
 
 -- * Type 'Parser'
 -- | Convenient alias.
similarity index 96%
rename from Hdoc/TCT/Read/Elem.hs
rename to src/Textphile/TCT/Read/Elem.hs
index f5338e45025f203a6c269732aae771f0dddc87ba..f9904390f99c96deb8a19b7a9c9ccd8ddb851884 100644 (file)
@@ -2,7 +2,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE Rank2Types #-}
 {-# LANGUAGE TypeFamilies #-}
-module Hdoc.TCT.Read.Elem where
+module Textphile.TCT.Read.Elem where
 
 import Control.Applicative (Applicative(..), Alternative(..))
 import Control.Monad (Monad(..))
@@ -20,10 +20,10 @@ import qualified Symantic.XML as XML
 import qualified Text.Megaparsec as P
 import qualified Text.Megaparsec.Char as P
 
-import Hdoc.TCT.Debug
-import Hdoc.TCT.Elem
-import Hdoc.TCT.Tree
-import Hdoc.TCT.Read.Cell
+import Textphile.TCT.Debug
+import Textphile.TCT.Elem
+import Textphile.TCT.Tree
+import Textphile.TCT.Read.Cell
 
 -- * Word
 p_Spaces :: P.Tokens s ~ TL.Text => Parser e s TL.Text
similarity index 98%
rename from Hdoc/TCT/Read/Token.hs
rename to src/Textphile/TCT/Read/Token.hs
index 166cb1c568cb33ff824b13a91cc75dbb695b9cfd..dcd86349237817fa1927cf8f0f045b397563a5bb 100644 (file)
@@ -5,7 +5,7 @@
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.TCT.Read.Token where
+module Textphile.TCT.Read.Token where
 
 import Control.Applicative (Applicative(..), Alternative(..))
 import Control.Monad (Monad(..))
@@ -35,12 +35,12 @@ import qualified Symantic.XML as XML
 import qualified Text.Megaparsec as P
 import qualified Text.Megaparsec.Char as P
 
-import Hdoc.TCT.Debug
-import Hdoc.TCT.Cell
-import Hdoc.TCT.Elem
-import Hdoc.TCT.Tree
-import Hdoc.TCT.Read.Elem
-import Hdoc.TCT.Read.Cell
+import Textphile.TCT.Debug
+import Textphile.TCT.Cell
+import Textphile.TCT.Elem
+import Textphile.TCT.Tree
+import Textphile.TCT.Read.Elem
+import Textphile.TCT.Read.Cell
 
 -- * Type 'Pairs'
 -- | Right-only Dyck language,
similarity index 96%
rename from Hdoc/TCT/Read/Tree.hs
rename to src/Textphile/TCT/Read/Tree.hs
index bae4f8bdd10ee6d5c2f11fd71a411af41aae95b7..23ea5b1b1ffe69666842c7b6bbab32a02f2a4ea4 100644 (file)
@@ -3,7 +3,7 @@
 {-# LANGUAGE Rank2Types #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeFamilies #-}
-module Hdoc.TCT.Read.Tree where
+module Textphile.TCT.Read.Tree where
 
 import Control.Applicative (Applicative(..), Alternative(..))
 import Control.Monad (Monad(..), void)
@@ -25,13 +25,13 @@ import qualified Symantic.XML as XML
 import qualified Text.Megaparsec as P
 import qualified Text.Megaparsec.Char as P
 
-import Hdoc.TCT.Debug
-import Hdoc.TCT.Cell
-import Hdoc.TCT.Elem
-import Hdoc.TCT.Tree
-import Hdoc.TCT.Read.Cell
-import Hdoc.TCT.Read.Elem
-import Hdoc.TCT.Read.Token
+import Textphile.TCT.Debug
+import Textphile.TCT.Cell
+import Textphile.TCT.Elem
+import Textphile.TCT.Tree
+import Textphile.TCT.Read.Cell
+import Textphile.TCT.Read.Elem
+import Textphile.TCT.Read.Token
 
 p_CellHeader :: P.Tokens s ~ TL.Text => Row -> Parser e s Row
 p_CellHeader row = debugParser "CellHeader" $ do
similarity index 99%
rename from Hdoc/TCT/Tree.hs
rename to src/Textphile/TCT/Tree.hs
index d20e0c310a4df66117a27267e24987286db3fb43..9b82ce0554395c31fc1f262356c4eb9b4e0c2b41 100644 (file)
@@ -1,8 +1,8 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE PatternSynonyms #-}
 {-# LANGUAGE ViewPatterns #-}
-module Hdoc.TCT.Tree
- ( module Hdoc.TCT.Tree
+module Textphile.TCT.Tree
+ ( module Textphile.TCT.Tree
  , Tree(..), Trees
  ) where
 
@@ -29,10 +29,10 @@ import qualified Data.Sequence as Seq
 import qualified Data.Text.Lazy as TL
 import qualified Text.Megaparsec as P
 
-import Hdoc.TCT.Utils
-import Hdoc.TCT.Cell
-import Hdoc.TCT.Elem
-import Hdoc.TCT.Debug
+import Textphile.TCT.Utils
+import Textphile.TCT.Cell
+import Textphile.TCT.Elem
+import Textphile.TCT.Debug
 
 -- * Type 'Root'
 -- | A single 'Tree' to gather all the 'Node's
similarity index 91%
rename from Hdoc/TCT/Utils.hs
rename to src/Textphile/TCT/Utils.hs
index a488daa5b423f9bb74e3968825b0055c52cb1fa4..b086c58f2357b63b3b9893bf1b22597234182ded 100644 (file)
@@ -1,4 +1,4 @@
-module Hdoc.TCT.Utils where
+module Textphile.TCT.Utils where
 
 import Data.Function ((.), flip)
 import Data.Functor (Functor, (<$>))
similarity index 98%
rename from Hdoc/TCT/Write/HTML5.hs
rename to src/Textphile/TCT/Write/HTML5.hs
index 8fdb75d0c3a36817df1252ff775b5c4a080e068e..62d17e6ac38c791be30be890099115e3ea38d51e 100644 (file)
@@ -2,7 +2,7 @@
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE ViewPatterns #-}
-module Hdoc.TCT.Write.HTML5 where
+module Textphile.TCT.Write.HTML5 where
 
 import Control.Monad (Monad(..), forM_, mapM_, join)
 import Data.Bool
@@ -32,13 +32,13 @@ import qualified Text.Blaze.Html5 as H
 import qualified Text.Blaze.Html5.Attributes as HA
 import qualified Text.Blaze.Internal as Blaze
 
--- import Hdoc.TCT.Debug
-import Hdoc.TCT
-import Hdoc.TCT.Utils
+-- import Textphile.TCT.Debug
+import Textphile.TCT
+import Textphile.TCT.Utils
 import Control.Monad.Utils
 import Text.Blaze.Utils
 import Text.Blaze.XML ()
-import qualified Hdoc.TCT.Write.Plain as Plain
+import qualified Textphile.TCT.Write.Plain as Plain
 
 writeHTML5 :: Trees (Cell Node) -> Html
 writeHTML5 body = do
similarity index 98%
rename from Hdoc/TCT/Write/Plain.hs
rename to src/Textphile/TCT/Write/Plain.hs
index ae870fcca4a8aa4012cac2ed13001ae90dfc9c48..e92e4f4b2edd7ba1247f1ba28c228bc5119f6418 100644 (file)
@@ -2,7 +2,7 @@
 {-# LANGUAGE OverloadedStrings #-}
 {-# LANGUAGE StrictData #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.TCT.Write.Plain where
+module Textphile.TCT.Write.Plain where
 
 import Control.Applicative (liftA2)
 import Control.Monad (Monad(..))
@@ -31,9 +31,9 @@ import qualified Data.Text.Lazy.Builder as TLB
 import qualified Symantic.XML as XML
 import qualified Text.Megaparsec as P
 
-import Hdoc.TCT
-import Hdoc.TCT.Utils
--- import Hdoc.TCT.Debug
+import Textphile.TCT
+import Textphile.TCT.Utils
+-- import Textphile.TCT.Debug
 
 writePlain :: Roots -> TL.Text
 writePlain doc = text (setStart doc def) doc
similarity index 98%
rename from Hdoc/TCT/Write/XML.hs
rename to src/Textphile/TCT/Write/XML.hs
index 26f940cc794a8fd44ccab61c2b4d5c101f83021b..83d3e6afe0b4169d4becb6aa9b32506dac53c05e 100644 (file)
@@ -1,9 +1,10 @@
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE OverloadedLists #-}
+{-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE ViewPatterns #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.TCT.Write.XML where
+module Textphile.TCT.Write.XML where
 
 import Control.Applicative (Applicative(..))
 import Control.Monad (Monad(..))
@@ -30,13 +31,13 @@ import qualified Data.List as List
 import qualified Data.Set as Set
 import qualified Data.Sequence as Seq
 import qualified Data.Text.Lazy as TL
-import qualified Hdoc.TCT.Write.Plain as Plain
+import qualified Textphile.TCT.Write.Plain as Plain
 import qualified Symantic.XML as XML
 
--- import Hdoc.TCT.Debug
-import Hdoc.TCT as TCT hiding (Parser)
-import Hdoc.TCT.Utils
-import Hdoc.XML (XML, XMLs)
+-- import Textphile.TCT.Debug
+import Textphile.TCT as TCT hiding (Parser)
+import Textphile.TCT.Utils
+import Textphile.XML (XML, XMLs)
 import Text.Blaze.DTC (xmlns_dtc)
 import Text.Blaze.XML ()
 
similarity index 98%
rename from Hdoc/Utils.hs
rename to src/Textphile/Utils.hs
index 85ddc10b719fbe3934a68b4552dc98f079552e77..3b616f38aea241cb344c3a78fd61354decbf9e94 100644 (file)
@@ -1,7 +1,7 @@
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# LANGUAGE OverloadedStrings #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.Utils where
+module Textphile.Utils where
 
 import Control.Monad (Monad(..))
 import Data.Bool
similarity index 94%
rename from Hdoc/XML.hs
rename to src/Textphile/XML.hs
index 912737c5c0eebd94a777fbbc4a708b2a6579c0f9..88db8db3b322f75cf14cd07cb2e9ff49803d2f0a 100644 (file)
@@ -1,7 +1,7 @@
 {-# LANGUAGE GeneralizedNewtypeDeriving #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
-module Hdoc.XML
- ( module Hdoc.XML
+module Textphile.XML
+ ( module Textphile.XML
  , XML.Node(..)
  ) where
 
@@ -21,8 +21,8 @@ import qualified Data.Sequence as Seq
 import qualified Data.Text.Lazy as TL
 import qualified Symantic.XML as XML
 
-import qualified Hdoc.TCT.Cell as TCT
-import Hdoc.Utils (Nat1)
+import qualified Textphile.TCT.Cell as TCT
+import Textphile.Utils (Nat1)
 
 -- * Type 'XML'
 type XML  = XML.XML  TCT.Location
similarity index 100%
rename from style/dtc-errors.js
rename to src/style/dtc-errors.js
similarity index 100%
rename from style/dtc-html5.css
rename to src/style/dtc-html5.css
diff --git a/src/style/dtc-html5.js b/src/style/dtc-html5.js
new file mode 100644 (file)
index 0000000..e69de29
similarity index 100%
rename from style/dtc-index.css
rename to src/style/dtc-index.css
similarity index 100%
rename from style/dtc-table.css
rename to src/style/dtc-table.css
similarity index 100%
rename from style/dtc-xml.css
rename to src/style/dtc-xml.css
similarity index 100%
rename from style/tct-html5.css
rename to src/style/tct-html5.css
index fc66eeca9f4ed4db9c33a367a95515e56b3805bd..ace557336e79ebc51b84f675c4ead0eaea41d71b 100644 (file)
@@ -1,10 +1,10 @@
-resolver: lts-14.13
+resolver: lts-14.27
 extra-deps:
 - ../treemap
 - ../treeseq
 - ../localization
 - ../symantic-cli
 - ../symantic-xml
-- ../symantic/symantic-document
-- ../hjugement
+- ../symantic-document
+- ../judgmentphile/judgmentphile-majority
 - monad-classes-0.3.2.2@sha256:793faead28dafb47f115c4dec877ce3e3ffab604f134d852652385632ea0923f
similarity index 73%
rename from hdoc.cabal
rename to textphile.cabal
index c49120b47386be29d34e6d96251917c7305d583a..73c7a7a1d55df0076efd43a89d1ee07942956d3a 100644 (file)
@@ -1,4 +1,4 @@
-name: hdoc
+name: textphile
 -- PVP:  +-+------- breaking API changes
 --       | | +----- non-breaking API additions
 --       | | | +--- code changes with no API change
@@ -13,29 +13,29 @@ description: Handle documents in:
 extra-doc-files:
 license: GPL-3
 license-file: COPYING
-author:      Julien Moutinho <julm+hdoc@autogeree.net>
-maintainer:  Julien Moutinho <julm+hdoc@autogeree.net>
-bug-reports: Julien Moutinho <julm+hdoc@autogeree.net>
+author:      Julien Moutinho <julm+textphile@sourcephile.fr>
+maintainer:  Julien Moutinho <julm+textphile@sourcephile.fr>
+bug-reports: Julien Moutinho <julm+textphile@sourcephile.fr>
 -- homepage:
 
 build-type: Simple
 cabal-version: >= 1.18
 tested-with: GHC==8.6.5
 data-files:
-  style/dtc-errors.css
-  style/dtc-errors.js
-  style/dtc-html5.css
-  style/dtc-html5.js
-  style/dtc-index.css
-  style/dtc-judgment.css
-  style/dtc-table.css
-  style/tct-html5.css
+  src/style/dtc-errors.css
+  src/style/dtc-errors.js
+  src/style/dtc-html5.css
+  src/style/dtc-html5.js
+  src/style/dtc-index.css
+  src/style/dtc-judgment.css
+  src/style/dtc-table.css
+  src/style/tct-html5.css
 extra-source-files:
   stack.yaml
 extra-tmp-files:
 
 Source-Repository head
- location: git://git.autogeree.net/hdoc
+ location: git://git.sourcephile.fr/textphile
  type:     git
 
 Flag debug
@@ -49,45 +49,46 @@ Flag prof
   Manual:      True
 
 Library
+  hs-source-dirs: src
   exposed-modules:
     Control.Monad.Utils
-    Hdoc.DTC.Analyze.Collect
-    Hdoc.DTC.Analyze.Index
-    Hdoc.DTC.Analyze.Check
-    Hdoc.DTC.Document
-    Hdoc.DTC.Read.TCT
-    Hdoc.DTC.Sym
-    Hdoc.DTC.Write.HTML5.Ident
-    Hdoc.DTC.Write.HTML5.Base
-    Hdoc.DTC.Write.HTML5.Judgment
-    Hdoc.DTC.Write.HTML5.Error
-    Hdoc.DTC.Write.HTML5
-    Hdoc.DTC.Write.Plain
-    Hdoc.DTC.Write.XML
-    Hdoc.RNC
-    Hdoc.TCT
-    Hdoc.TCT.Cell
-    Hdoc.TCT.Debug
-    Hdoc.TCT.Elem
-    Hdoc.TCT.Read
-    Hdoc.TCT.Read.Cell
-    Hdoc.TCT.Read.Elem
-    Hdoc.TCT.Read.Token
-    Hdoc.TCT.Read.Tree
-    Hdoc.TCT.Tree
-    Hdoc.TCT.Utils
-    Hdoc.TCT.Write.HTML5
-    Hdoc.TCT.Write.Plain
-    Hdoc.TCT.Write.XML
-    Hdoc.Utils
-    Hdoc.XML
+    Textphile.DTC.Analyze.Collect
+    Textphile.DTC.Analyze.Index
+    Textphile.DTC.Analyze.Check
+    Textphile.DTC.Document
+    Textphile.DTC.Read.TCT
+    Textphile.DTC.Sym
+    Textphile.DTC.Write.HTML5.Ident
+    Textphile.DTC.Write.HTML5.Base
+    Textphile.DTC.Write.HTML5.Judgment
+    Textphile.DTC.Write.HTML5.Error
+    Textphile.DTC.Write.HTML5
+    Textphile.DTC.Write.Plain
+    Textphile.DTC.Write.XML
+    Textphile.RNC
+    Textphile.TCT
+    Textphile.TCT.Cell
+    Textphile.TCT.Debug
+    Textphile.TCT.Elem
+    Textphile.TCT.Read
+    Textphile.TCT.Read.Cell
+    Textphile.TCT.Read.Elem
+    Textphile.TCT.Read.Token
+    Textphile.TCT.Read.Tree
+    Textphile.TCT.Tree
+    Textphile.TCT.Utils
+    Textphile.TCT.Write.HTML5
+    Textphile.TCT.Write.Plain
+    Textphile.TCT.Write.XML
+    Textphile.Utils
+    Textphile.XML
     Text.Blaze.DTC
     Text.Blaze.DTC.Attributes
     Text.Blaze.HTML5
     Text.Blaze.Utils
     Text.Blaze.XML
   other-modules:
-    Paths_hdoc
+    Paths_textphile
   default-language: Haskell2010
   default-extensions:
     LambdaCase
@@ -118,7 +119,7 @@ Library
     , directory >= 1.3
     , filepath >= 1.4
     , hashable >= 1.2.6
-    , hjugement >= 0.0
+    , judgmentphile-majority >= 0.0
     , hxt-charproperties >= 9.2
     , localization >= 1.0.1
     , symantic-cli >= 0.0.0
@@ -136,11 +137,15 @@ Library
     , treeseq >= 1.0
     , unordered-containers >= 0.2.8
 
-Executable hdoc
-  hs-source-dirs: exe/cli
+Executable textphile
+  hs-source-dirs: cli
   main-is: Main.hs
   other-modules:
-    Paths_hdoc
+    Paths_textphile
+    Textphile.CLI
+    Textphile.CLI.Compile
+    Textphile.CLI.Lang
+    Textphile.CLI.Utils
   default-language: Haskell2010
   default-extensions:
     ConstraintKinds
@@ -153,6 +158,7 @@ Executable hdoc
     MultiParamTypeClasses
     NamedFieldPuns
     NoImplicitPrelude
+    NoMonomorphismRestriction
     PatternGuards
     PolyKinds
     Rank2Types
@@ -174,7 +180,7 @@ Executable hdoc
     cpp-options: -DPROFILING
     ghc-options: -fprof-auto -rtsopts
   build-depends:
-    hdoc
+    textphile
     , ansi-terminal >= 0.4
     , base >= 4.6 && < 5
     , blaze-html >= 0.9
@@ -198,17 +204,19 @@ Executable hdoc
     , symantic-cli >= 0.0
     , symantic-xml >= 0.0
     , strict >= 0.3
+    , terminal-size >= 0.3
     , text >= 1.2
     , time >= 1.8
     , transformers >= 0.4
     , treeseq >= 1.0
     , unordered-containers >= 0.2.8
+    , unix >= 2.7
     -- , mono-traversable
     -- , safe >= 0.2
     -- , safe-exceptions >= 0.1
     -- , treemap
 
---Test-Suite hdoc-test
+--Test-Suite textphile-test
 --  type: exitcode-stdio-1.0
 --  hs-source-dirs: test
 --  main-is: Main.hs
@@ -230,7 +238,7 @@ Executable hdoc
 --    -fno-warn-tabs
 --    -fhide-source-paths
 --  build-depends:
---    hdoc
+--    textphile
 --    , base >= 4.10 && < 5
 --    , blaze-html >= 0.9
 --    , blaze-markup >= 0.8