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