Move SiteGenerator into executable only and rename library to Byg.*
This commit is contained in:
parent
0f0bde5f18
commit
a60f652242
|
@ -1,10 +1,11 @@
|
||||||
module Main where
|
module Main where
|
||||||
|
|
||||||
import Types (Dependency)
|
import Byg.Types (Dependency)
|
||||||
import qualified DependencyRunner as DR
|
import qualified Byg.DependencyRunner as DR
|
||||||
import qualified Types.Dependency as D
|
import qualified Byg.Types.Dependency as D
|
||||||
|
import Byg.DependencyGenerator (evalDepGenM)
|
||||||
|
|
||||||
import SiteGenerator (generateSite)
|
import SiteGenerator (generateSite)
|
||||||
import DependencyGenerator (evalDepGenM)
|
|
||||||
|
|
||||||
import System.Environment (getArgs)
|
import System.Environment (getArgs)
|
||||||
import qualified Data.Text.IO as T
|
import qualified Data.Text.IO as T
|
|
@ -1,8 +1,8 @@
|
||||||
module SiteGenerator (generateSite) where
|
module SiteGenerator (generateSite) where
|
||||||
|
|
||||||
import Types (Token(..), Date(..), formatDate, formatDateShort)
|
import Byg.Types (Token(..), Date(..), formatDate, formatDateShort)
|
||||||
import DependencyGenerator
|
import Byg.DependencyGenerator
|
||||||
import Functions
|
import Byg.Functions
|
||||||
|
|
||||||
import Data.List (sort, elemIndex)
|
import Data.List (sort, elemIndex)
|
||||||
import Data.Function ((&))
|
import Data.Function ((&))
|
|
@ -20,23 +20,22 @@ library
|
||||||
import: common
|
import: common
|
||||||
hs-source-dirs: src
|
hs-source-dirs: src
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
Types.Token
|
Byg.Types.Token
|
||||||
Types.Value
|
Byg.Types.Value
|
||||||
Types.Functions
|
Byg.Types.Functions
|
||||||
Types.Dependency
|
Byg.Types.Dependency
|
||||||
Types.Date
|
Byg.Types.Date
|
||||||
Types
|
Byg.Types
|
||||||
DependencyGenerator
|
Byg.DependencyGenerator
|
||||||
Functions.Image
|
Byg.Functions.Image
|
||||||
Functions.Pandoc
|
Byg.Functions.Pandoc
|
||||||
Functions.Paths
|
Byg.Functions.Paths
|
||||||
Functions.Template
|
Byg.Functions.Template
|
||||||
Functions.Text
|
Byg.Functions.Text
|
||||||
Functions.Date
|
Byg.Functions.Date
|
||||||
Functions.Atom
|
Byg.Functions.Atom
|
||||||
Functions
|
Byg.Functions
|
||||||
DependencyRunner
|
Byg.DependencyRunner
|
||||||
SiteGenerator
|
|
||||||
build-depends:
|
build-depends:
|
||||||
base >=4.14 && <4.20
|
base >=4.14 && <4.20
|
||||||
, mtl
|
, mtl
|
||||||
|
@ -52,7 +51,10 @@ library
|
||||||
|
|
||||||
executable byg
|
executable byg
|
||||||
import: common
|
import: common
|
||||||
main-is: src/Main.hs
|
hs-source-dirs: app
|
||||||
|
main-is: Main.hs
|
||||||
|
other-modules:
|
||||||
|
SiteGenerator
|
||||||
build-depends:
|
build-depends:
|
||||||
base >=4.14 && <4.20
|
base >=4.14 && <4.20
|
||||||
, byg
|
, byg
|
||||||
|
|
|
@ -3,7 +3,7 @@ pkgs.haskell.lib.overrideCabal
|
||||||
(haskell.callCabal2nix "byg" ./. { })
|
(haskell.callCabal2nix "byg" ./. { })
|
||||||
(_: {
|
(_: {
|
||||||
configureFlags = [
|
configureFlags = [
|
||||||
# "--ghc-option=-Werror"
|
"--ghc-option=-Werror"
|
||||||
"--ghc-option=-O2"
|
"--ghc-option=-O2"
|
||||||
];
|
];
|
||||||
doHaddock = false;
|
doHaddock = false;
|
||||||
|
|
|
@ -1,6 +1,6 @@
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
{-# LANGUAGE FunctionalDependencies #-}
|
{-# LANGUAGE FunctionalDependencies #-}
|
||||||
module DependencyGenerator
|
module Byg.DependencyGenerator
|
||||||
( DepGenM
|
( DepGenM
|
||||||
, DepGenM'
|
, DepGenM'
|
||||||
, TokenableTo(..)
|
, TokenableTo(..)
|
||||||
|
@ -26,9 +26,9 @@ module DependencyGenerator
|
||||||
, unzipDepGenM
|
, unzipDepGenM
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types.Token (Token(..))
|
import Byg.Types.Token (Token(..))
|
||||||
import Types.Functions (IsFunctionIO(..))
|
import Byg.Types.Functions (IsFunctionIO(..))
|
||||||
import Types.Dependency (Action(..), F(..), Dependency, makeDependency)
|
import Byg.Types.Dependency (Action(..), F(..), Dependency, makeDependency)
|
||||||
|
|
||||||
import Type.Reflection (Typeable, TypeRep, typeRep)
|
import Type.Reflection (Typeable, TypeRep, typeRep)
|
||||||
import Control.Monad.State (MonadState, State, runState, put, get)
|
import Control.Monad.State (MonadState, State, runState, put, get)
|
|
@ -1,5 +1,5 @@
|
||||||
{-# LANGUAGE MonoLocalBinds #-}
|
{-# LANGUAGE MonoLocalBinds #-}
|
||||||
module DependencyRunner
|
module Byg.DependencyRunner
|
||||||
( DepRunM
|
( DepRunM
|
||||||
, runDeps
|
, runDeps
|
||||||
, runDepRunMIO
|
, runDepRunMIO
|
||||||
|
@ -7,15 +7,14 @@ module DependencyRunner
|
||||||
, extractSndTokenAsList
|
, extractSndTokenAsList
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (evalFunctionIO, functionIOReads, functionIOWrites)
|
import Byg.Types (evalFunctionIO, functionIOReads, functionIOWrites)
|
||||||
import Types.Value
|
import Byg.Types.Value
|
||||||
import Types.Token
|
import Byg.Types.Token
|
||||||
import Types.Dependency
|
import Byg.Types.Dependency
|
||||||
|
|
||||||
import Type.Reflection (Typeable)
|
import Type.Reflection (Typeable)
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
import qualified Data.Map as M
|
import qualified Data.Map as M
|
||||||
import Data.Maybe (catMaybes)
|
|
||||||
import Control.Monad (void, forM, filterM)
|
import Control.Monad (void, forM, filterM)
|
||||||
import Control.Monad.State (MonadState, MonadIO, StateT, evalStateT, get, modify, liftIO)
|
import Control.Monad.State (MonadState, MonadIO, StateT, evalStateT, get, modify, liftIO)
|
||||||
import Control.Monad.Writer (MonadWriter, WriterT, runWriterT, tell)
|
import Control.Monad.Writer (MonadWriter, WriterT, runWriterT, tell)
|
||||||
|
@ -55,8 +54,8 @@ runDep (Dependency _ a action _ b) =
|
||||||
else putTokenValue b $ NotEvaluated m
|
else putTokenValue b $ NotEvaluated m
|
||||||
where m :: LastUpdated -> DepRunM (Maybe (Value, LastUpdated))
|
where m :: LastUpdated -> DepRunM (Maybe (Value, LastUpdated))
|
||||||
m luFuture = do
|
m luFuture = do
|
||||||
m <- runAction action a luFuture
|
mr <- runAction action a luFuture
|
||||||
case m of
|
case mr of
|
||||||
Just (result, luResult) -> do
|
Just (result, luResult) -> do
|
||||||
putTokenValue b $ Evaluated result luResult
|
putTokenValue b $ Evaluated result luResult
|
||||||
pure $ Just (result, luResult)
|
pure $ Just (result, luResult)
|
||||||
|
@ -80,10 +79,10 @@ getTokenValueByIndex luFuture i = do
|
||||||
Nothing -> pure Nothing
|
Nothing -> pure Nothing
|
||||||
Just x -> evaluate luFuture x
|
Just x -> evaluate luFuture x
|
||||||
|
|
||||||
minimumOrNever :: [LastUpdated] -> LastUpdated
|
-- minimumOrNever :: [LastUpdated] -> LastUpdated
|
||||||
minimumOrNever = \case
|
-- minimumOrNever = \case
|
||||||
[] -> Never
|
-- [] -> Never
|
||||||
times -> minimum times
|
-- times -> minimum times
|
||||||
|
|
||||||
maximumOrNever :: [LastUpdated] -> LastUpdated
|
maximumOrNever :: [LastUpdated] -> LastUpdated
|
||||||
maximumOrNever = \case
|
maximumOrNever = \case
|
||||||
|
@ -250,8 +249,8 @@ runAction action tokenInput luFuture = case action of
|
||||||
result <- forM input $ \x -> do
|
result <- forM input $ \x -> do
|
||||||
putTokenValue innerInput $ Evaluated (toValue x) (max luInput lastUpdated)
|
putTokenValue innerInput $ Evaluated (toValue x) (max luInput lastUpdated)
|
||||||
runDeps subDeps
|
runDeps subDeps
|
||||||
m <- getTokenValue innerOutput luFuture
|
mr <- getTokenValue innerOutput luFuture
|
||||||
pure $ do (vOut, luOut) <- m
|
pure $ do (vOut, luOut) <- mr
|
||||||
pure (fromValue vOut, luOut)
|
pure (fromValue vOut, luOut)
|
||||||
pure $ do result' <- sequence result
|
pure $ do result' <- sequence result
|
||||||
let (values, lus) = unzip result'
|
let (values, lus) = unzip result'
|
|
@ -0,0 +1,17 @@
|
||||||
|
module Byg.Functions
|
||||||
|
( module Byg.Functions.Image
|
||||||
|
, module Byg.Functions.Pandoc
|
||||||
|
, module Byg.Functions.Paths
|
||||||
|
, module Byg.Functions.Template
|
||||||
|
, module Byg.Functions.Text
|
||||||
|
, module Byg.Functions.Date
|
||||||
|
, module Byg.Functions.Atom
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Byg.Functions.Image
|
||||||
|
import Byg.Functions.Pandoc
|
||||||
|
import Byg.Functions.Paths
|
||||||
|
import Byg.Functions.Template
|
||||||
|
import Byg.Functions.Text
|
||||||
|
import Byg.Functions.Date
|
||||||
|
import Byg.Functions.Atom
|
|
@ -1,12 +1,12 @@
|
||||||
{-# LANGUAGE RebindableSyntax #-}
|
{-# LANGUAGE RebindableSyntax #-}
|
||||||
module Functions.Atom
|
module Byg.Functions.Atom
|
||||||
( generateAtom
|
( generateAtom
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Types (Token, Date(..), formatDateShort)
|
import Byg.Types (Token, Date(..), formatDateShort)
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), onTupleToken)
|
import Byg.DependencyGenerator (DepGenM, TokenableTo(..), onTupleToken)
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
|
@ -1,9 +1,9 @@
|
||||||
module Functions.Date
|
module Byg.Functions.Date
|
||||||
( extractDate
|
( extractDate
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (Token, Date(..))
|
import Byg.Types (Token, Date(..))
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), onToken)
|
import Byg.DependencyGenerator (DepGenM, TokenableTo(..), onToken)
|
||||||
|
|
||||||
import Data.List.NonEmpty (NonEmpty(..))
|
import Data.List.NonEmpty (NonEmpty(..))
|
||||||
import qualified Data.List.NonEmpty as NE
|
import qualified Data.List.NonEmpty as NE
|
|
@ -1,4 +1,4 @@
|
||||||
module Functions.Image
|
module Byg.Functions.Image
|
||||||
( Image(..)
|
( Image(..)
|
||||||
, ImageConversionSettings(..)
|
, ImageConversionSettings(..)
|
||||||
, openImage
|
, openImage
|
||||||
|
@ -6,10 +6,10 @@ module Functions.Image
|
||||||
, convertImage
|
, convertImage
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (IsFunctionIO(..), Token(..))
|
import Byg.Types (IsFunctionIO(..), Token(..))
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), onTupleToken, toTupleToken,
|
import Byg.DependencyGenerator (DepGenM, TokenableTo(..), onTupleToken, toTupleToken,
|
||||||
runFunctionIO, runFunctionIO_)
|
runFunctionIO, runFunctionIO_)
|
||||||
import DependencyRunner (extractSndTokenAsList)
|
import Byg.DependencyRunner (extractSndTokenAsList)
|
||||||
|
|
||||||
import qualified Codec.Picture as CP
|
import qualified Codec.Picture as CP
|
||||||
import qualified Codec.Picture.STBIR as CPS
|
import qualified Codec.Picture.STBIR as CPS
|
|
@ -1,4 +1,4 @@
|
||||||
module Functions.Pandoc
|
module Byg.Functions.Pandoc
|
||||||
( readMarkdown
|
( readMarkdown
|
||||||
, writeHtml
|
, writeHtml
|
||||||
, markdownToHtml
|
, markdownToHtml
|
||||||
|
@ -6,8 +6,8 @@ module Functions.Pandoc
|
||||||
, injectAfterTitle
|
, injectAfterTitle
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (Token)
|
import Byg.Types (Token)
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), onToken, onTupleToken)
|
import Byg.DependencyGenerator (DepGenM, TokenableTo(..), onToken, onTupleToken)
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Control.Monad ((>=>))
|
import Control.Monad ((>=>))
|
|
@ -1,4 +1,4 @@
|
||||||
module Functions.Paths
|
module Byg.Functions.Paths
|
||||||
( joinPaths
|
( joinPaths
|
||||||
, fileComponents
|
, fileComponents
|
||||||
, hasExtension
|
, hasExtension
|
||||||
|
@ -9,10 +9,10 @@ module Functions.Paths
|
||||||
, copyTo
|
, copyTo
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (IsFunctionIO(..), Token(..))
|
import Byg.Types (IsFunctionIO(..), Token(..))
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), onToken, onTupleToken, toTupleToken,
|
import Byg.DependencyGenerator (DepGenM, TokenableTo(..), onToken, onTupleToken, toTupleToken,
|
||||||
runFunctionIO, runFunctionIO_, untupleSndDepGenM)
|
runFunctionIO, runFunctionIO_, untupleSndDepGenM)
|
||||||
import DependencyRunner (extractSndTokenAsList)
|
import Byg.DependencyRunner (extractSndTokenAsList)
|
||||||
|
|
||||||
import Data.Char (toLower)
|
import Data.Char (toLower)
|
||||||
import Control.Monad (when)
|
import Control.Monad (when)
|
|
@ -1,11 +1,11 @@
|
||||||
module Functions.Template
|
module Byg.Functions.Template
|
||||||
( Template(..)
|
( Template(..)
|
||||||
, makeTemplate
|
, makeTemplate
|
||||||
, applyTemplate
|
, applyTemplate
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (Token)
|
import Byg.Types (Token)
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), onTupleToken)
|
import Byg.DependencyGenerator (DepGenM, TokenableTo(..), onTupleToken)
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as T
|
import qualified Data.Text as T
|
|
@ -1,12 +1,12 @@
|
||||||
module Functions.Text
|
module Byg.Functions.Text
|
||||||
( readTextFile
|
( readTextFile
|
||||||
, saveTextFile
|
, saveTextFile
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (IsFunctionIO(..), Token(..))
|
import Byg.Types (IsFunctionIO(..), Token(..))
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), toTupleToken,
|
import Byg.DependencyGenerator (DepGenM, TokenableTo(..), toTupleToken,
|
||||||
runFunctionIO, runFunctionIO_)
|
runFunctionIO, runFunctionIO_)
|
||||||
import DependencyRunner (extractSndTokenAsList)
|
import Byg.DependencyRunner (extractSndTokenAsList)
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text.IO as T
|
import qualified Data.Text.IO as T
|
|
@ -0,0 +1,13 @@
|
||||||
|
module Byg.Types
|
||||||
|
( module Byg.Types.Token
|
||||||
|
, module Byg.Types.Value
|
||||||
|
, module Byg.Types.Functions
|
||||||
|
, module Byg.Types.Date
|
||||||
|
, Dependency
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Byg.Types.Token
|
||||||
|
import Byg.Types.Value
|
||||||
|
import Byg.Types.Functions
|
||||||
|
import Byg.Types.Date
|
||||||
|
import Byg.Types.Dependency (Dependency)
|
|
@ -1,4 +1,4 @@
|
||||||
module Types.Date
|
module Byg.Types.Date
|
||||||
( Date(..)
|
( Date(..)
|
||||||
, formatDate
|
, formatDate
|
||||||
, formatDateShort
|
, formatDateShort
|
|
@ -1,5 +1,5 @@
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
module Types.Dependency
|
module Byg.Types.Dependency
|
||||||
( Action(..)
|
( Action(..)
|
||||||
, F(..)
|
, F(..)
|
||||||
, Dependency(..)
|
, Dependency(..)
|
||||||
|
@ -12,8 +12,8 @@ module Types.Dependency
|
||||||
, formatDependencyTrees
|
, formatDependencyTrees
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types.Token (Token(..))
|
import Byg.Types.Token (Token(..))
|
||||||
import Types.Functions (IsFunctionIO(..))
|
import Byg.Types.Functions (IsFunctionIO(..))
|
||||||
|
|
||||||
import Type.Reflection (Typeable, TypeRep, typeRep)
|
import Type.Reflection (Typeable, TypeRep, typeRep)
|
||||||
import Text.Printf (printf)
|
import Text.Printf (printf)
|
|
@ -1,9 +1,10 @@
|
||||||
{-# LANGUAGE FunctionalDependencies #-}
|
{-# LANGUAGE FunctionalDependencies #-}
|
||||||
module Types.Functions
|
module Byg.Types.Functions
|
||||||
( IsFunctionIO(..)
|
( IsFunctionIO(..)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types.Token (Token)
|
import Byg.Types.Token (Token)
|
||||||
|
|
||||||
import Type.Reflection (Typeable)
|
import Type.Reflection (Typeable)
|
||||||
|
|
||||||
class (Show f, Show a, Typeable a, Show b, Typeable b) => IsFunctionIO f a b | f -> a b where
|
class (Show f, Show a, Typeable a, Show b, Typeable b) => IsFunctionIO f a b | f -> a b where
|
|
@ -1,5 +1,5 @@
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
module Types.Token
|
module Byg.Types.Token
|
||||||
( Token(..)
|
( Token(..)
|
||||||
) where
|
) where
|
||||||
|
|
|
@ -1,5 +1,5 @@
|
||||||
{-# LANGUAGE MonoLocalBinds #-}
|
{-# LANGUAGE MonoLocalBinds #-}
|
||||||
module Types.Value
|
module Byg.Types.Value
|
||||||
( Value(..)
|
( Value(..)
|
||||||
, toValue
|
, toValue
|
||||||
, toValueRep
|
, toValueRep
|
|
@ -1,17 +0,0 @@
|
||||||
module Functions
|
|
||||||
( module Functions.Image
|
|
||||||
, module Functions.Pandoc
|
|
||||||
, module Functions.Paths
|
|
||||||
, module Functions.Template
|
|
||||||
, module Functions.Text
|
|
||||||
, module Functions.Date
|
|
||||||
, module Functions.Atom
|
|
||||||
) where
|
|
||||||
|
|
||||||
import Functions.Image
|
|
||||||
import Functions.Pandoc
|
|
||||||
import Functions.Paths
|
|
||||||
import Functions.Template
|
|
||||||
import Functions.Text
|
|
||||||
import Functions.Date
|
|
||||||
import Functions.Atom
|
|
|
@ -1,13 +0,0 @@
|
||||||
module Types
|
|
||||||
( module Types.Token
|
|
||||||
, module Types.Value
|
|
||||||
, module Types.Functions
|
|
||||||
, module Types.Date
|
|
||||||
, Dependency
|
|
||||||
) where
|
|
||||||
|
|
||||||
import Types.Token
|
|
||||||
import Types.Value
|
|
||||||
import Types.Functions
|
|
||||||
import Types.Date
|
|
||||||
import Types.Dependency (Dependency)
|
|
Loading…
Reference in New Issue