Rewrite pandoc functions to be inline
This commit is contained in:
parent
d85243b1ba
commit
1da32745a2
|
@ -7,6 +7,7 @@ module DependencyGenerator
|
||||||
, toTupleToken
|
, toTupleToken
|
||||||
, evalDepGenM
|
, evalDepGenM
|
||||||
, inject
|
, inject
|
||||||
|
, onToken
|
||||||
, runFunction
|
, runFunction
|
||||||
, runFunctionIO
|
, runFunctionIO
|
||||||
, runFunctionIO_
|
, runFunctionIO_
|
||||||
|
@ -27,7 +28,7 @@ module DependencyGenerator
|
||||||
|
|
||||||
import Types.Token (Token(..))
|
import Types.Token (Token(..))
|
||||||
import Types.Functions (IsFunction(), IsFunctionIO(..))
|
import Types.Functions (IsFunction(), IsFunctionIO(..))
|
||||||
import Types.Dependency (Action(..), Dependency, makeDependency)
|
import 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)
|
||||||
|
@ -68,6 +69,11 @@ genDependency f = genDependencyM (pure . f)
|
||||||
inject :: (Show a, Typeable a) => a -> DepGenM (Token a)
|
inject :: (Show a, Typeable a) => a -> DepGenM (Token a)
|
||||||
inject x = genDependency (makeDependency NoToken (Inject x))
|
inject x = genDependency (makeDependency NoToken (Inject x))
|
||||||
|
|
||||||
|
onToken :: (TokenableTo a t, Show a, Typeable a, Show b, Typeable b) => (a -> b) -> t -> DepGenM (Token b)
|
||||||
|
onToken f input = do
|
||||||
|
input' <- toToken input
|
||||||
|
genDependency (makeDependency input' (InlineFunction (F f)))
|
||||||
|
|
||||||
runFunction :: IsFunction f a b => f -> Token a -> DepGenM (Token b)
|
runFunction :: IsFunction f a b => f -> Token a -> DepGenM (Token b)
|
||||||
runFunction f input = genDependency (makeDependency input (Function f))
|
runFunction f input = genDependency (makeDependency input (Function f))
|
||||||
|
|
||||||
|
|
|
@ -10,6 +10,7 @@ import Types.Value
|
||||||
import Types.Token
|
import Types.Token
|
||||||
import Types.Dependency
|
import Types.Dependency
|
||||||
|
|
||||||
|
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 Control.Monad (void, forM)
|
import Control.Monad (void, forM)
|
||||||
|
@ -49,24 +50,38 @@ runDep (Dependency _ a action _ b) =
|
||||||
putStrLn "----------"
|
putStrLn "----------"
|
||||||
pure result
|
pure result
|
||||||
|
|
||||||
|
getTokenValueByIndex :: Int -> DepRunM Value
|
||||||
|
getTokenValueByIndex i = do
|
||||||
|
m <- get
|
||||||
|
evaluate (m M.! i)
|
||||||
|
|
||||||
|
getTokenValueRaw :: Token a -> DepRunM a
|
||||||
|
getTokenValueRaw token = case token of
|
||||||
|
Token i ->
|
||||||
|
fromValue <$> getTokenValueByIndex i
|
||||||
|
TupleToken a b -> do
|
||||||
|
(,) <$> getTokenValueRaw a <*> getTokenValueRaw b
|
||||||
|
ZipToken a b -> do
|
||||||
|
zip <$> getTokenValueRaw a <*> getTokenValueRaw b
|
||||||
|
ListToken ts -> do
|
||||||
|
mapM getTokenValueRaw ts
|
||||||
|
NoToken ->
|
||||||
|
pure ()
|
||||||
|
|
||||||
getTokenValue :: Token a -> DepRunM Value
|
getTokenValue :: Token a -> DepRunM Value
|
||||||
getTokenValue token = case token of
|
getTokenValue token = case token of
|
||||||
Token i -> do
|
Token i ->
|
||||||
m <- get
|
getTokenValueByIndex i
|
||||||
evaluate (m M.! i)
|
TupleToken _ _ ->
|
||||||
TupleToken a b -> do
|
fromRaw token
|
||||||
va <- getTokenValue a
|
ZipToken _ _ ->
|
||||||
vb <- getTokenValue b
|
fromRaw token
|
||||||
pure $ toValueRep (tokenTypeRep token) (fromValue va, fromValue vb)
|
ListToken _ ->
|
||||||
ZipToken a b -> do
|
fromRaw token
|
||||||
va <- getTokenValue a
|
|
||||||
vb <- getTokenValue b
|
|
||||||
pure $ toValueRep (tokenTypeRep token) $ zip (fromValue va) (fromValue vb)
|
|
||||||
ListToken ts -> do
|
|
||||||
vs <- mapM getTokenValue ts
|
|
||||||
pure $ toValueRep (tokenTypeRep token) (map fromValue vs)
|
|
||||||
NoToken ->
|
NoToken ->
|
||||||
pure $ toValue ()
|
fromRaw token
|
||||||
|
where fromRaw :: (Typeable a, Show a) => Token a -> DepRunM Value
|
||||||
|
fromRaw = fmap toValue . getTokenValueRaw
|
||||||
|
|
||||||
putTokenValue :: Token a -> ValueExistence -> DepRunM ()
|
putTokenValue :: Token a -> ValueExistence -> DepRunM ()
|
||||||
putTokenValue t e = case t of
|
putTokenValue t e = case t of
|
||||||
|
@ -77,29 +92,34 @@ putTokenValue t e = case t of
|
||||||
_ ->
|
_ ->
|
||||||
error "unexpected"
|
error "unexpected"
|
||||||
|
|
||||||
runAction :: Action a b -> Value -> DepRunM Value
|
runAction :: forall a b. Action a b -> Value -> DepRunM Value
|
||||||
runAction action input = case action of
|
runAction action input = case action of
|
||||||
Function f ->
|
Function f ->
|
||||||
pure $ toValue $ evalFunction f $ fromValue input
|
calc (evalFunction f)
|
||||||
InlineFunction (F f) ->
|
InlineFunction (F f) ->
|
||||||
pure $ toValue $ f $ fromValue input
|
calc f
|
||||||
FunctionIO f ->
|
FunctionIO f ->
|
||||||
liftIO (toValue <$> evalFunctionIO f (fromValue input))
|
calcM (liftIO . evalFunctionIO f)
|
||||||
Inject x ->
|
Inject x ->
|
||||||
pure $ toValue x
|
pure $ toValue x
|
||||||
FilterComp ->
|
FilterComp ->
|
||||||
let (vs, mask) = fromValue input
|
calc (\(vs, mask) -> map fst $ filter snd $ zip vs mask)
|
||||||
in pure $ toValueRep (actionTargetType action) $ map fst $ filter snd $ zip vs mask
|
|
||||||
UntupleFst ->
|
UntupleFst ->
|
||||||
pure $ toValue $ fst $ fromValueRep (actionSourceType action) input
|
calc fst
|
||||||
UntupleSnd ->
|
UntupleSnd ->
|
||||||
pure $ toValue $ snd $ fromValueRep (actionSourceType action) input
|
calc snd
|
||||||
UnzipFst ->
|
UnzipFst ->
|
||||||
pure $ toValue $ map fst $ fromValueRep (actionSourceType action) input
|
calc (map fst)
|
||||||
UnzipSnd ->
|
UnzipSnd ->
|
||||||
pure $ toValue $ map snd $ fromValueRep (actionSourceType action) input
|
calc (map snd)
|
||||||
MapComp subDeps innerInput innerOutput ->
|
MapComp subDeps innerInput innerOutput ->
|
||||||
(toValueRep (actionTargetType action) <$>) $ forM (fromValueRep (actionSourceType action) input) $ \x -> do
|
(toValueRep (actionTargetType action) <$>)
|
||||||
|
$ forM (fromValueRep (actionSourceType action) input) $ \x -> do
|
||||||
putTokenValue innerInput $ Evaluated $ toValue x
|
putTokenValue innerInput $ Evaluated $ toValue x
|
||||||
runDeps subDeps
|
runDeps subDeps
|
||||||
fromValue <$> getTokenValue innerOutput
|
fromValue <$> getTokenValue innerOutput
|
||||||
|
where calcM :: (Typeable a, Typeable b, Show b) => (a -> DepRunM b) -> DepRunM Value
|
||||||
|
calcM f = toValue <$> (f $ fromValueRep (actionSourceType action) input)
|
||||||
|
|
||||||
|
calc :: (Typeable a, Typeable b, Show b) => (a -> b) -> DepRunM Value
|
||||||
|
calc f = calcM (pure . f)
|
||||||
|
|
|
@ -4,8 +4,8 @@ module Functions.Pandoc
|
||||||
, extractTitle
|
, extractTitle
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Types (IsFunction(..), Token)
|
import Types (Token)
|
||||||
import DependencyGenerator (DepGenM, TokenableTo(..), runFunction)
|
import DependencyGenerator (DepGenM, TokenableTo(..), onToken)
|
||||||
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Text.Pandoc.Definition (Pandoc)
|
import Text.Pandoc.Definition (Pandoc)
|
||||||
|
@ -18,31 +18,15 @@ runPandoc m = case P.runPure m of
|
||||||
Left e -> error ("unexpected pandoc error: " ++ show e)
|
Left e -> error ("unexpected pandoc error: " ++ show e)
|
||||||
Right result -> result
|
Right result -> result
|
||||||
|
|
||||||
data ReadMarkdown = ReadMarkdown deriving Show
|
|
||||||
instance IsFunction ReadMarkdown Text Pandoc where
|
|
||||||
evalFunction ReadMarkdown contents =
|
|
||||||
let settings = P.def { P.readerExtensions = P.extensionsFromList [ P.Ext_raw_html ] }
|
|
||||||
in runPandoc $ P.readMarkdown settings contents
|
|
||||||
|
|
||||||
readMarkdown :: TokenableTo Text a => a -> DepGenM (Token Pandoc)
|
readMarkdown :: TokenableTo Text a => a -> DepGenM (Token Pandoc)
|
||||||
readMarkdown a = runFunction ReadMarkdown =<< toToken a
|
readMarkdown = onToken $ \contents ->
|
||||||
|
let settings = P.def { P.readerExtensions = P.extensionsFromList [ P.Ext_raw_html ] }
|
||||||
|
in runPandoc $ P.readMarkdown settings contents
|
||||||
data WriteHtml = WriteHtml deriving Show
|
|
||||||
instance IsFunction WriteHtml Pandoc Text where
|
|
||||||
evalFunction WriteHtml pandoc =
|
|
||||||
runPandoc
|
|
||||||
$ P.writeHtml5String P.def pandoc
|
|
||||||
|
|
||||||
writeHtml :: TokenableTo Pandoc a => a -> DepGenM (Token Text)
|
writeHtml :: TokenableTo Pandoc a => a -> DepGenM (Token Text)
|
||||||
writeHtml a = runFunction WriteHtml =<< toToken a
|
writeHtml = onToken $ \pandoc -> runPandoc $ P.writeHtml5String P.def pandoc
|
||||||
|
|
||||||
|
|
||||||
data ExtractTitle = ExtractTitle deriving Show
|
|
||||||
instance IsFunction ExtractTitle Pandoc Text where
|
|
||||||
evalFunction ExtractTitle (PD.Pandoc _ blocks) = case blocks of
|
|
||||||
(PD.Header 1 _ inlines : _) -> PS.stringify inlines
|
|
||||||
_ -> error "unexpected"
|
|
||||||
|
|
||||||
extractTitle :: TokenableTo Pandoc a => a -> DepGenM (Token Text)
|
extractTitle :: TokenableTo Pandoc a => a -> DepGenM (Token Text)
|
||||||
extractTitle a = runFunction ExtractTitle =<< toToken a
|
extractTitle = onToken $ \(PD.Pandoc _ blocks) -> case blocks of
|
||||||
|
(PD.Header 1 _ inlines : _) -> PS.stringify inlines
|
||||||
|
_ -> error "unexpected"
|
||||||
|
|
|
@ -38,7 +38,7 @@ instance Show (F a b) where
|
||||||
show = const "<function>"
|
show = const "<function>"
|
||||||
|
|
||||||
data Dependency where
|
data Dependency where
|
||||||
Dependency :: (Typeable a, Show a) => TypeRep a -> Token a -> Action a b -> TypeRep b -> Token b -> Dependency
|
Dependency :: TypeRep a -> Token a -> Action a b -> TypeRep b -> Token b -> Dependency
|
||||||
deriving instance Show Dependency
|
deriving instance Show Dependency
|
||||||
|
|
||||||
makeDependency :: (Typeable a, Show a, Typeable b, Show b) => Token a -> Action a b -> Token b -> Dependency
|
makeDependency :: (Typeable a, Show a, Typeable b, Show b) => Token a -> Action a b -> Token b -> Dependency
|
||||||
|
|
|
@ -1,10 +1,9 @@
|
||||||
{-# LANGUAGE GADTs #-}
|
{-# LANGUAGE GADTs #-}
|
||||||
module Types.Token
|
module Types.Token
|
||||||
( Token(..)
|
( Token(..)
|
||||||
, tokenTypeRep
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Type.Reflection (Typeable, TypeRep, typeRep)
|
import Type.Reflection (Typeable)
|
||||||
|
|
||||||
data Token a where
|
data Token a where
|
||||||
Token :: (Typeable a, Show a) => Int -> Token a
|
Token :: (Typeable a, Show a) => Int -> Token a
|
||||||
|
@ -14,6 +13,3 @@ data Token a where
|
||||||
NoToken :: Token ()
|
NoToken :: Token ()
|
||||||
|
|
||||||
deriving instance Show (Token a)
|
deriving instance Show (Token a)
|
||||||
|
|
||||||
tokenTypeRep :: Typeable a => Token a -> TypeRep a
|
|
||||||
tokenTypeRep _ = typeRep
|
|
||||||
|
|
Loading…
Reference in New Issue