Skip to content

Commit

Permalink
Restore cache.json stripping behaviour
Browse files Browse the repository at this point in the history
  • Loading branch information
srid committed Jan 19, 2021
1 parent fa9ce2b commit 969901d
Show file tree
Hide file tree
Showing 6 changed files with 36 additions and 26 deletions.
4 changes: 2 additions & 2 deletions neuron/src/app/Neuron/Reactor/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ import Neuron.Plugin (PluginRegistry)
import qualified Neuron.Plugin as Plugin
import Neuron.Version (neuronVersion)
import qualified Neuron.Zettelkasten.Graph.Build as G
import Neuron.Zettelkasten.Graph.Type (ZettelGraph, stripSurroundingContext)
import Neuron.Zettelkasten.Graph.Type (ZettelGraph)
import Neuron.Zettelkasten.ID (ZettelID (..))
import qualified Neuron.Zettelkasten.Resolver as R
import Neuron.Zettelkasten.Zettel (ZettelC)
Expand Down Expand Up @@ -178,7 +178,7 @@ loadZettelkastenFromFiles config fileTree = do
log D $ "Plugins enabled: " <> Plugin.pluginRegistryShow plugins
((g, zs), errs) <- loadZettelkastenFromFilesWithPlugins plugins fileTree
let cache = Cache.NeuronCache g errs config neuronVersion
cacheSmall = cache {Cache._neuronCache_graph = stripSurroundingContext g}
cacheSmall = cache {Cache._neuronCache_graph = Plugin.stripSurroundingContext g}
Cache.updateCache cacheSmall
pure (cache, zs, fileTree)

Expand Down
24 changes: 22 additions & 2 deletions neuron/src/lib/Neuron/Plugin.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,8 +14,9 @@ import Control.Monad.Writer
import Data.Dependent.Map (DMap)
import qualified Data.Dependent.Map as DMap
import Data.Dependent.Sum (DSum (..))
import qualified Data.Graph.Labelled as Algo
import qualified Data.Map.Strict as Map
import Data.Some (Some (..), withSome)
import Data.Some
import qualified Data.Text as T
import Neuron.Frontend.Route (NeuronWebT)
import Neuron.Frontend.Route.Data.Types
Expand Down Expand Up @@ -145,4 +146,23 @@ renderHandleLink' = \case
PluginZettelRouteData_Tags :=> Identity x ->
Tags.renderHandleLink x
PluginZettelRouteData_NeuronIgnore :=> _ ->
const Nothing
const Nothing

preJsonStrip :: Zettel -> Zettel
preJsonStrip z =
let pluginData' = flip fmap (DMap.toList $ zettelPluginData z) $ \case
x@(PluginZettelData_NeuronIgnore :=> Identity ()) ->
x
x@(PluginZettelData_DirTree :=> Identity _) ->
x
x@(PluginZettelData_Tags :=> Identity _) ->
x
PluginZettelData_Links :=> Identity x ->
PluginZettelData_Links :=> Identity (Links.preJsonStrip x)
in z {zettelPluginData = DMap.fromList pluginData'}

-- | Compress the graph to save space, by eliminating the unnecessary
-- surrounding context Pandoc blocks.
stripSurroundingContext :: ZettelGraph -> ZettelGraph
stripSurroundingContext =
Algo.emap (fmap (second $ const mempty)) . Algo.vmap preJsonStrip
6 changes: 6 additions & 0 deletions neuron/src/lib/Neuron/Plugin/Plugins/Links.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@ module Neuron.Plugin.Plugins.Links
routePluginData,
renderHandleLink,
renderPanel,
preJsonStrip,
)
where

Expand Down Expand Up @@ -140,6 +141,11 @@ parseQueryLink attrs url = do
guard $ not $ "/" `T.isInfixOf` s || ":" `T.isInfixOf` s
pure s

preJsonStrip :: [((ZettelID, Connection), [Block])] -> [((ZettelID, Connection), [Block])]
preJsonStrip conns =
-- Discard surrounding context
conns <&> second (const empty)

-- Query evaluation
-- ----------------

Expand Down
7 changes: 5 additions & 2 deletions neuron/src/lib/Neuron/Plugin/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -49,7 +49,9 @@ data Plugin routeData = Plugin
-- | Plugin-specific HTML rendering to do on the zettel pages.
_plugin_renderPanel :: forall t m. (DomBuilder t m, PostBuild t m) => (Pandoc -> NeuronWebT t m ()) -> routeData -> NeuronWebT t m (),
-- | Hooks for rendering custom DOM elements; here, url links.
_plugin_renderHandleLink :: forall t m. (PandocBuilder t m, PostBuild t m) => routeData -> Text -> Maybe (NeuronWebT t m ())
_plugin_renderHandleLink :: forall t m. (PandocBuilder t m, PostBuild t m) => routeData -> Text -> Maybe (NeuronWebT t m ()),
-- | Strip data you don't want in JSON dumps
_plugin_preJsonStrip :: Zettel -> Zettel
}

instance Default a => Default (Plugin a) where
Expand All @@ -62,5 +64,6 @@ instance Default a => Default (Plugin a) where
_plugin_graphConnections = const $ pure mempty,
_plugin_routeData = def,
_plugin_renderPanel = \_ _ -> blank,
_plugin_renderHandleLink = \_ _ -> Nothing
_plugin_renderHandleLink = \_ _ -> Nothing,
_plugin_preJsonStrip = id
}
10 changes: 1 addition & 9 deletions neuron/src/lib/Neuron/Zettelkasten/Graph/Type.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,14 +6,12 @@
module Neuron.Zettelkasten.Graph.Type
( -- * Graph type
ZettelGraph,
stripSurroundingContext,
)
where

import Data.Graph.Labelled (LabelledGraph)
import qualified Data.Graph.Labelled as Algo
import Neuron.Zettelkasten.Connection
import Neuron.Zettelkasten.Zettel (Zettel, sansLinkContext)
import Neuron.Zettelkasten.Zettel (Zettel)
import Relude

-- | The Zettelkasten graph
Expand All @@ -23,9 +21,3 @@ import Relude
-- our case, and is effectively the same as there not being an edge between
-- those vertices.
type ZettelGraph = LabelledGraph Zettel (Maybe ContextualConnection)

-- | Compress the graph to save space, by eliminating the unnecessary
-- surrounding context Pandoc blocks.
stripSurroundingContext :: ZettelGraph -> ZettelGraph
stripSurroundingContext =
Algo.emap (fmap (second $ const mempty)) . Algo.vmap sansLinkContext
11 changes: 0 additions & 11 deletions neuron/src/lib/Neuron/Zettelkasten/Zettel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -165,17 +165,6 @@ sansContent = \case
{ zettelContent = Tagged Nothing
}

-- | Strip out the link context data
--
-- Useful to to minimize the impending JSON dump.
sansLinkContext :: ZettelT c -> ZettelT c
sansLinkContext z =
-- TODO: strip in plugin!
-- z {zettelQueries = stripContextFromZettelQuery <$> zettelQueries z}
-- where
-- stripContextFromZettelQuery (someQ, _ctx) = (someQ, mempty)
z

instance Show (ZettelT c) where
show Zettel {..} = "Zettel:" <> show zettelID

Expand Down

0 comments on commit 969901d

Please sign in to comment.