module Emanote.Model.Stork ( renderStorkIndex, ) where import Control.Monad.Logger (MonadLoggerIO) import Data.IxSet.Typed qualified as Ix import Emanote.Model.Note qualified as N import Emanote.Model.Stork.Index (File (File), Input (Input), readOrBuildStorkIndex) import Emanote.Model.Title qualified as Tit import Emanote.Model.Type (Model) import Emanote.Model.Type qualified as M import Emanote.Route qualified as R import Emanote.Route.SiteRoute qualified as SR import Emanote.Source.Loc qualified as Loc import Optics.Core ((^.)) import Relude import System.FilePath ((</>)) renderStorkIndex :: (MonadIO m, MonadLoggerIO m) => Model -> m LByteString renderStorkIndex :: forall (m :: Type -> Type). (MonadIO m, MonadLoggerIO m) => Model -> m LByteString renderStorkIndex Model model = do IndexVar -> Input -> m LByteString forall (m :: Type -> Type). (MonadIO m, MonadLoggerIO m) => IndexVar -> Input -> m LByteString readOrBuildStorkIndex (Model model Model -> Optic' A_Lens NoIx Model IndexVar -> IndexVar forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic' A_Lens NoIx Model IndexVar forall (encF :: Type -> Type). Lens' (ModelT encF) IndexVar M.modelStorkIndex) ([File] -> Input Input ([File] -> Input) -> [File] -> Input forall a b. (a -> b) -> a -> b $ Model -> [File] storkFiles Model model) storkFiles :: Model -> [File] storkFiles :: Model -> [File] storkFiles Model model = let baseDir :: FilePath baseDir = Loc -> FilePath Loc.locPath (Loc -> FilePath) -> (LocLayers -> Loc) -> LocLayers -> FilePath forall b c a. (b -> c) -> (a -> b) -> a -> c . HasCallStack => LocLayers -> Loc LocLayers -> Loc Loc.primaryLayer (LocLayers -> FilePath) -> LocLayers -> FilePath forall a b. (a -> b) -> a -> b $ Model model Model -> Optic' A_Lens NoIx Model LocLayers -> LocLayers forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic' A_Lens NoIx Model LocLayers forall (encF :: Type -> Type). Lens' (ModelT encF) LocLayers M.modelLayers in IxSet NoteIxs Note -> [Note] forall (ixs :: IxList) a. IxSet ixs a -> [a] Ix.toList (Model model Model -> Optic' A_Lens NoIx Model (IxSet NoteIxs Note) -> IxSet NoteIxs Note forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic' A_Lens NoIx Model (IxSet NoteIxs Note) forall (encF :: Type -> Type). Lens' (ModelT encF) (IxSet NoteIxs Note) M.modelNotes) [Note] -> (Note -> File) -> [File] forall (f :: Type -> Type) a b. Functor f => f a -> (a -> b) -> f b <&> \Note note -> FilePath -> Text -> Text -> File File ((FilePath baseDir FilePath -> FilePath -> FilePath </>) (FilePath -> FilePath) -> FilePath -> FilePath forall a b. (a -> b) -> a -> b $ (forall (lmlType :: LML). HasExt @SourceExt ('LMLType lmlType) => R @SourceExt ('LMLType lmlType) -> FilePath) -> LMLRoute -> FilePath forall r. (forall (lmlType :: LML). HasExt @SourceExt ('LMLType lmlType) => R @SourceExt ('LMLType lmlType) -> r) -> LMLRoute -> r R.withLmlRoute forall a (ft :: FileType a). HasExt @a ft => R @a ft -> FilePath forall (lmlType :: LML). HasExt @SourceExt ('LMLType lmlType) => R @SourceExt ('LMLType lmlType) -> FilePath R.encodeRoute (LMLRoute -> FilePath) -> LMLRoute -> FilePath forall a b. (a -> b) -> a -> b $ Note note Note -> Optic' A_Lens NoIx Note LMLRoute -> LMLRoute forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic' A_Lens NoIx Note LMLRoute N.noteRoute) (HasCallStack => Model -> SiteRoute -> Text Model -> SiteRoute -> Text SR.siteRouteUrl Model model (SiteRoute -> Text) -> SiteRoute -> Text forall a b. (a -> b) -> a -> b $ LMLRoute -> SiteRoute SR.lmlSiteRoute (LMLRoute -> SiteRoute) -> LMLRoute -> SiteRoute forall a b. (a -> b) -> a -> b $ Note note Note -> Optic' A_Lens NoIx Note LMLRoute -> LMLRoute forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic' A_Lens NoIx Note LMLRoute N.noteRoute) (Title -> Text Tit.toPlain (Title -> Text) -> Title -> Text forall a b. (a -> b) -> a -> b $ Note note Note -> Optic' A_Lens NoIx Note Title -> Title forall k s (is :: IxList) a. Is k A_Getter => s -> Optic' k is s a -> a ^. Optic' A_Lens NoIx Note Title N.noteTitle)