This commit is contained in:
maralorn 2022-11-19 23:52:06 +01:00
parent de5db368c2
commit eab81666d8
3 changed files with 3 additions and 15 deletions

View file

@ -109,7 +109,7 @@
buildInputs = [
pre-commit-hooks.defaultPackage.${system}
haskellPackages.haskell-language-server
# haskellPackages.weeder
pkgs.haskell.packages.ghc92.weeder
pkgs.haskellPackages.cabal-install
pkgs.pv
];

View file

@ -1,8 +1,7 @@
module NOM.Util (foldMapEndo, forMaybeM, addPrintCache, diffTime, relTimeToSeconds) where
module NOM.Util (foldMapEndo, forMaybeM, diffTime, relTimeToSeconds) where
import Data.Time (NominalDiffTime)
import Relude
import Relude.Extra (toSnd)
import Streamly.Internal.Data.Time.Units (AbsTime, MilliSecond64 (..), RelTime, diffAbsTime, fromRelTime)
foldMapEndo :: Foldable f => (b -> a -> a) -> f b -> a -> a
@ -11,17 +10,6 @@ foldMapEndo f = appEndo . foldMap (Endo . f)
forMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m [b]
forMaybeM = flip mapMaybeM
-- Like in 'flow'
{-# INLINE addPrintCache #-}
addPrintCache :: Functor m => (update -> (istate, state) -> m (errors, (istate, Maybe state))) -> (state -> cache) -> update -> (istate, state, cache) -> m (errors, (istate, state, cache))
addPrintCache updater cacher update (!oldIState, !oldState, oldCache) =
updater update (oldIState, oldState) <&> \(errors, (istate, stateMay)) ->
let (!newState, newCache) = maybe (oldState, oldCache) (toSnd cacher) stateMay
in (errors, (istate, newState, newCache))
diffTime :: AbsTime -> AbsTime -> NominalDiffTime
diffTime = fmap relTimeToSeconds . diffAbsTime
relTimeToSeconds :: RelTime -> NominalDiffTime
relTimeToSeconds rel_time = case fromRelTime rel_time of
MilliSecond64 milli_sec -> fromInteger $ toInteger milli_sec `div` 1000

View file

@ -1 +1 @@
{ roots = [ "^Paths_.", "^Main.main$" ], type-class-roots = True }
{ roots = [ "^Paths_.", "^Main.main$", "showCode$" ], type-class-roots = True }