Skip to content

Commit

Permalink
Merge pull request #481 from shivaraj-bh/update-nixpkgs
Browse files Browse the repository at this point in the history
Update `nixpkgs`
  • Loading branch information
srid authored Dec 19, 2023
2 parents 524f891 + 826ce3d commit 23fb2f0
Show file tree
Hide file tree
Showing 30 changed files with 297 additions and 249 deletions.
4 changes: 2 additions & 2 deletions emanote/emanote.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -43,8 +43,6 @@ common haskell-common
-fprint-explicit-foralls -fprint-explicit-kinds

default-extensions:
NoImplicitPrelude
NoStarIsType
BangPatterns
ConstraintKinds
DataKinds
Expand All @@ -70,6 +68,8 @@ common haskell-common
LambdaCase
MultiParamTypeClasses
MultiWayIf
NoImplicitPrelude
NoStarIsType
NumericUnderscores
OverloadedStrings
PolyKinds
Expand Down
27 changes: 16 additions & 11 deletions emanote/src/Emanote.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,8 +67,8 @@ run cfg@EmanoteConfig {..} = do
>>= postRun cfg
CLI.Cmd_Export -> do
Dynamic (unModelEma -> model0, _) <-
flip runLoggerLoggingT oneOffLogger $
siteInput @SiteRoute (Ema.CLI.action def) cfg
flip runLoggerLoggingT oneOffLogger
$ siteInput @SiteRoute (Ema.CLI.action def) cfg
putLBSLn $ Export.renderJSONExport model0
where
-- A logger suited for running one-off commands.
Expand All @@ -84,8 +84,8 @@ run cfg@EmanoteConfig {..} = do

postRun :: EmanoteConfig -> (Model.ModelEma, (FilePath, [FilePath])) -> IO ()
postRun EmanoteConfig {..} (unModelEma -> model0, (outPath, genPaths)) = do
when (model0 ^. modelCompileTailwind) $
compileTailwindCss (outPath </> generatedCssFile) genPaths
when (model0 ^. modelCompileTailwind)
$ compileTailwindCss (outPath </> generatedCssFile) genPaths
checkBrokenLinks _emanoteConfigCli $ Export.modelRels model0
checkBadMarkdownFiles $ Model.modelNoteErrors model0

Expand All @@ -104,8 +104,9 @@ checkBadMarkdownFiles noteErrs = runStderrLoggingT $ do

checkBrokenLinks :: CLI.Cli -> Map LMLRoute [Export.Link] -> IO ()
checkBrokenLinks cli modelRels = runStderrLoggingT $ do
((), res :: Sum Int) <- runWriterT $
forM_ (Map.toList modelRels) $ \(noteRoute, rels) ->
((), res :: Sum Int) <- runWriterT
$ forM_ (Map.toList modelRels)
$ \(noteRoute, rels) ->
forM_ (sortNub rels) $ \(Export.Link urt rrt) ->
case rrt of
RRTFound _ -> pass
Expand All @@ -127,11 +128,15 @@ compileTailwindCss :: (MonadUnliftIO m) => FilePath -> [FilePath] -> m ()
compileTailwindCss cssPath genPaths = do
runStdoutLoggingT $ do
log $ "Running Tailwind CSS v3 compiler to generate: " <> toText cssPath
Tailwind.runTailwind $
def
& Tailwind.tailwindConfig % Tailwind.tailwindConfigContent .~ genPaths
& Tailwind.tailwindOutput .~ cssPath
& Tailwind.tailwindMode .~ Tailwind.Production
Tailwind.runTailwind
$ def
& Tailwind.tailwindConfig
% Tailwind.tailwindConfigContent
.~ genPaths
& Tailwind.tailwindOutput
.~ cssPath
& Tailwind.tailwindMode
.~ Tailwind.Production

defaultEmanotePandocRenderers :: EmanotePandocRenderers Model.Model LMLRoute
defaultEmanotePandocRenderers =
Expand Down
4 changes: 2 additions & 2 deletions emanote/src/Emanote/CLI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ cliParser cwd = do
pure Cli {..}
where
pathList defaultPath = do
option pathListReader $
mconcat
option pathListReader
$ mconcat
[ long "layers"
, short 'L'
, metavar "LAYERS"
Expand Down
9 changes: 5 additions & 4 deletions emanote/src/Emanote/Model/Calendar.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,9 +44,10 @@ parseRouteDay =
-- Day
day <- asInt =<< replicateM 2 M.digitChar
-- Optional suffix (ignored)
void $
optional $ do
void
$ optional
$ do
void $ M.oneOf ['-', '_', ' ']
void M.takeRest
maybe (fail "Not a date") pure $
fromGregorianValid year (fromInteger month) (fromInteger day)
maybe (fail "Not a date") pure
$ fromGregorianValid year (fromInteger month) (fromInteger day)
9 changes: 5 additions & 4 deletions emanote/src/Emanote/Model/Graph.hs
Original file line number Diff line number Diff line change
Expand Up @@ -115,10 +115,11 @@ lookupNoteByWikiLink model wl = do

modelLookupBacklinks :: R.LMLRoute -> Model -> [(R.LMLRoute, NonEmpty [B.Block])]
modelLookupBacklinks r model =
sortOn (Calendar.backlinkSortKey model . fst) $
groupNE $
backlinkRels r model <&> \rel ->
(rel ^. Rel.relFrom, rel ^. Rel.relCtx)
sortOn (Calendar.backlinkSortKey model . fst)
$ groupNE
$ backlinkRels r model
<&> \rel ->
(rel ^. Rel.relFrom, rel ^. Rel.relCtx)
where
groupNE :: forall a b. (Ord a) => [(a, b)] -> [(a, NonEmpty b)]
groupNE =
Expand Down
9 changes: 5 additions & 4 deletions emanote/src/Emanote/Model/Link/Rel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -67,8 +67,9 @@ noteRels note =
where
extractLinks :: Map Text (NonEmpty ([(Text, Text)], [B.Block])) -> IxRel
extractLinks m =
Ix.fromList $
flip concatMap (Map.toList m) $ \(url, instances) -> do
Ix.fromList
$ flip concatMap (Map.toList m)
$ \(url, instances) -> do
flip mapMaybe (toList instances) $ \(attrs, ctx) -> do
let parentR = R.withLmlRoute R.routeParent $ note ^. noteRoute
(target, _manchor) <- parseUnresolvedRelTarget parentR attrs url
Expand Down Expand Up @@ -103,8 +104,8 @@ parseUnresolvedRelTarget baseDir attrs url = do

relocateRelUrlUnder :: Maybe FilePath -> FilePath -> FilePath
relocateRelUrlUnder mbase fp =
normalizeIgnoringSymlinks $
case mbase of
normalizeIgnoringSymlinks
$ case mbase of
Nothing -> fp
Just x -> x </> fp

Expand Down
4 changes: 2 additions & 2 deletions emanote/src/Emanote/Model/Link/Resolve.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,8 @@ resolveUnresolvedRelTarget model = \case
resolveModelRoute model r
<&> resourceSiteRoute
Rel.URTVirtual virtualRoute -> do
Rel.RRTFound $
SR.SiteRoute_VirtualRoute
Rel.RRTFound
$ SR.SiteRoute_VirtualRoute
virtualRoute

resolveWikiLinkMustExist ::
Expand Down
99 changes: 53 additions & 46 deletions emanote/src/Emanote/Model/Note.hs
Original file line number Diff line number Diff line change
Expand Up @@ -149,8 +149,9 @@ queryNoteTitle r doc meta =
getPandocTitle doc
R.LMLRoute_Org _ ->
getPandocMetaTitle doc
in fromMaybe (doc, fileNameTitle) $
fmap (doc,) yamlNoteTitle <|> fmap (withoutH1 doc,) notePandocTitle
in fromMaybe (doc, fileNameTitle)
$ fmap (doc,) yamlNoteTitle
<|> fmap (withoutH1 doc,) notePandocTitle
where
getPandocTitle :: Pandoc -> Maybe Tit.Title
getPandocTitle =
Expand Down Expand Up @@ -208,15 +209,17 @@ ancestorPlaceholderNote r =
[ folderListingQuery
, -- TODO: Ideally, we should use semantic tags, like <aside> (rather
-- than <div>), to render these non-relevant content.
B.Div (cls "emanote:placeholder-message") . one . B.Para $
[ B.Str
"Note: To override the auto-generated content here, create a file named one of: "
, -- TODO: or, .org
B.Span (cls "font-mono text-sm") $
one $
B.Str $
oneOfLmlFilenames r
]
B.Div (cls "emanote:placeholder-message")
. one
. B.Para
$ [ B.Str
"Note: To override the auto-generated content here, create a file named one of: "
, -- TODO: or, .org
B.Span (cls "font-mono text-sm")
$ one
$ B.Str
$ oneOfLmlFilenames r
]
]
in mkEmptyNoteWith (R.defaultLmlRoute r) placeHolder
where
Expand All @@ -229,17 +232,18 @@ cls x =

missingNote :: R.R ext -> Text -> Note
missingNote route404 urlPath =
mkEmptyNoteWith (R.defaultLmlRoute route404) $
one $
B.Para
[ B.Str "No note has the URL "
, B.Code B.nullAttr $ "/" <> urlPath
, -- TODO: org
B.Span (cls "font-mono text-sm") $
one $
B.Str $
". You may create a file with that name, ie. one of: " <> oneOfLmlFilenames route404
]
mkEmptyNoteWith (R.defaultLmlRoute route404)
$ one
$ B.Para
[ B.Str "No note has the URL "
, B.Code B.nullAttr $ "/" <> urlPath
, -- TODO: org
B.Span (cls "font-mono text-sm")
$ one
$ B.Str
$ ". You may create a file with that name, ie. one of: "
<> oneOfLmlFilenames route404
]

oneOfLmlFilenames :: R ext -> Text
oneOfLmlFilenames r =
Expand All @@ -249,19 +253,20 @@ oneOfLmlFilenames r =

ambiguousNoteURL :: FilePath -> NonEmpty R.LMLRoute -> Note
ambiguousNoteURL urlPath rs =
mkEmptyNoteWith (head rs) $
[ B.Para
[ B.Str "The URL "
, B.Code B.nullAttr $ toText urlPath
, B.Str " is ambiguous, as more than one note (see list below) use it. To fix this, specify a different slug for these notes:"
]
]
<> one candidates
mkEmptyNoteWith (head rs)
$ [ B.Para
[ B.Str "The URL "
, B.Code B.nullAttr $ toText urlPath
, B.Str " is ambiguous, as more than one note (see list below) use it. To fix this, specify a different slug for these notes:"
]
]
<> one candidates
where
candidates :: B.Block
candidates =
B.BulletList $
toList rs <&> \(R.lmlRouteCase -> r) ->
B.BulletList
$ toList rs
<&> \(R.lmlRouteCase -> r) ->
[ B.Plain $ one $ B.Str " "
, B.Plain $ one $ B.Code B.nullAttr $ show r
]
Expand Down Expand Up @@ -353,12 +358,14 @@ applyNoteMetaFilters doc =
-- DESIGN: In retrospect, this is like a Pandoc lua filter?
addTagsFromBody frontmatter =
frontmatter
& AO.key "tags" % AO._Array
.~ ( fromList . fmap Aeson.toJSON $
ordNub $
SData.lookupAeson @[HT.Tag] mempty (one "tags") frontmatter
<> HT.inlineTagsInPandoc doc
)
& AO.key "tags"
% AO._Array
.~ ( fromList
. fmap Aeson.toJSON
$ ordNub
$ SData.lookupAeson @[HT.Tag] mempty (one "tags") frontmatter
<> HT.inlineTagsInPandoc doc
)
addDescriptionFromBody =
overrideAesonText ("page" :| ["description"]) $ \case
B.Para is -> [plainify is]
Expand All @@ -371,13 +378,13 @@ applyNoteMetaFilters doc =
_ -> mempty
overrideAesonText :: forall a. (W.Walkable a Pandoc) => NonEmpty Text -> (a -> [Text]) -> Aeson.Value -> Aeson.Value
overrideAesonText key f frontmatter =
SData.mergeAesons $
frontmatter
:| maybeToList
( do
guard $ "" == SData.lookupAeson @Text "" key frontmatter
val <- viaNonEmpty head $ W.query f doc
pure $ SData.oneAesonText (toList key) val
)
SData.mergeAesons
$ frontmatter
:| maybeToList
( do
guard $ "" == SData.lookupAeson @Text "" key frontmatter
val <- viaNonEmpty head $ W.query f doc
pure $ SData.oneAesonText (toList key) val
)

makeLenses ''Note
12 changes: 6 additions & 6 deletions emanote/src/Emanote/Model/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,12 +61,12 @@ queryParser = do
where
fromUserPath s =
if
| "*" `T.isInfixOf` s ->
QueryByPathPattern (toString s)
| "/" `T.isPrefixOf` s ->
QueryByPath (toString $ T.drop 1 s)
| otherwise ->
QueryByPathPattern (toString $ "**/" <> s <> "/**")
| "*" `T.isInfixOf` s ->
QueryByPathPattern (toString s)
| "/" `T.isPrefixOf` s ->
QueryByPath (toString $ T.drop 1 s)
| otherwise ->
QueryByPathPattern (toString $ "**/" <> s <> "/**")

runQuery :: R.LMLRoute -> Model -> Query -> [Note]
runQuery currentRoute model =
Expand Down
24 changes: 12 additions & 12 deletions emanote/src/Emanote/Model/StaticFile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -76,18 +76,18 @@ readStaticFileInfo ::
readStaticFileInfo fp readFilePath = do
let extension = toText (takeExtension fp)
if
| extension `elem` imageExts ->
pure $ Just StaticFileInfoImage
| extension `elem` videoExts ->
pure $ Just StaticFileInfoVideo
| extension `elem` audioExts ->
pure $ Just StaticFileInfoAudio
| extension == ".pdf" ->
pure $ Just StaticFileInfoPDF
| Just lang <- Map.lookup extension codeExts -> do
code <- readFilePath fp
pure $ Just $ StaticFileInfoCode lang code
| otherwise -> return Nothing
| extension `elem` imageExts ->
pure $ Just StaticFileInfoImage
| extension `elem` videoExts ->
pure $ Just StaticFileInfoVideo
| extension `elem` audioExts ->
pure $ Just StaticFileInfoAudio
| extension == ".pdf" ->
pure $ Just StaticFileInfoPDF
| Just lang <- Map.lookup extension codeExts -> do
code <- readFilePath fp
pure $ Just $ StaticFileInfoCode lang code
| otherwise -> return Nothing
where
imageExts = [".jpg", ".jpeg", ".png", ".svg", ".gif", ".bmp", ".webp"]
videoExts = [".mp4", ".webm", ".ogv"]
Expand Down
18 changes: 9 additions & 9 deletions emanote/src/Emanote/Model/Stork/Index.hs
Original file line number Diff line number Diff line change
Expand Up @@ -65,8 +65,8 @@ runStork :: (MonadIO m) => Config -> m LByteString
runStork config = do
let storkToml = handleTomlandBug $ Toml.encode configCodec config
(_, !index, _) <-
liftIO $
readProcessWithExitCode
liftIO
$ readProcessWithExitCode
storkBin
-- NOTE: Cannot use "--output -" due to bug in Rust or Stork:
-- https://github.com/jameslittle230/stork/issues/262
Expand Down Expand Up @@ -132,26 +132,26 @@ configCodec :: TomlCodec Config
configCodec =
Config
<$> Toml.table inputCodec "input"
.= configInput
.= configInput
where
inputCodec :: TomlCodec Input
inputCodec =
Input
<$> Toml.list fileCodec "files"
.= inputFiles
.= inputFiles
<*> Toml.diwrap (handlingCodec "frontmatter_handling")
.= inputFrontmatterHandling
.= inputFrontmatterHandling
fileCodec :: TomlCodec File
fileCodec =
File
<$> Toml.string "path"
.= filePath
.= filePath
<*> Toml.text "url"
.= fileUrl
.= fileUrl
<*> Toml.text "title"
.= fileTitle
.= fileTitle
<*> Toml.diwrap (filetypeCodec "filetype")
.= fileFiletype
.= fileFiletype
handlingCodec :: Toml.Key -> TomlCodec Handling
handlingCodec = textBy showHandling parseHandling
where
Expand Down
5 changes: 3 additions & 2 deletions emanote/src/Emanote/Model/Task.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,8 +44,9 @@ instance Indexable TaskIxs Task where
noteTasks :: Note -> IxTask
noteTasks note =
let taskListItems = TaskList.queryTasks $ note ^. N.noteDoc
in Ix.fromList $
zip [1 ..] taskListItems <&> \(idx, (checked, doc)) ->
in Ix.fromList
$ zip [1 ..] taskListItems
<&> \(idx, (checked, doc)) ->
Task (note ^. N.noteRoute) idx doc checked

makeLenses ''Task
Loading

0 comments on commit 23fb2f0

Please sign in to comment.