From 075e020dca3a673110a505e7cf17a93671b9a1d2 Mon Sep 17 00:00:00 2001 From: Justin Bedo Date: Mon, 30 Jan 2023 08:48:16 +1100 Subject: code formatting --- bin/cluster.hs | 14 +++++--------- 1 file changed, 5 insertions(+), 9 deletions(-) (limited to 'bin/cluster.hs') diff --git a/bin/cluster.hs b/bin/cluster.hs index 6c8ea52..d0328a6 100644 --- a/bin/cluster.hs +++ b/bin/cluster.hs @@ -1,6 +1,5 @@ -{-# LANGUAGE ViewPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE ViewPatterns #-} module Main where @@ -13,12 +12,12 @@ import GHC.Compact import Numeric.Log hiding (sum) import Options.Applicative import PPL hiding (binom) -import System.Random (mkStdGen, setStdGen, StdGen, random, split) import qualified Streaming as S +import Streaming.Prelude (Of, Stream, each, fold, yield) import qualified Streaming.Prelude as S -import Streaming.Prelude (each, fold, Of, Stream, yield) -import System.IO ( hSetBuffering, BufferMode(NoBuffering), stdout) +import System.IO (BufferMode (NoBuffering), hSetBuffering, stdout) import System.ProgressBar +import System.Random (StdGen, mkStdGen, random, setStdGen, split) cumsum = scanl1 (+) @@ -123,7 +122,6 @@ main = run =<< execParser opts [(r, "")] -> if r <= 1 && r > 0 then Right r else Left "mhfrac not a valid probability" _ -> Left "mhfrac not a valid probability" - takeWithProgress :: S.MonadIO m => Int -> Stream (Of a) m r -> Stream (Of a) m () takeWithProgress n str = do pb <- S.liftIO $ newProgressBar defStyle 10 (Progress 0 n ()) @@ -139,7 +137,7 @@ run opts = do g = mkStdGen $ seed opts parsed <- compact $ map (map dbl . tail . words) lines hSetBuffering stdout NoBuffering - ((ps, cl), _) <- S.fold_ (\l r -> if mml l < mml r then l else r) (([[]],[]), -1/0) id . takeWithProgress (nsamples opts) $ mh g (mhfrac opts) (model $ getCompact parsed) + ((ps, cl), _) <- S.fold_ (\l r -> if mml l < mml r then l else r) (([[]], []), -1 / 0) id . takeWithProgress (nsamples opts) $ mh g (mhfrac opts) (model $ getCompact parsed) writeFile (propsPath opts) . unlines $ map (intercalate "," . map show) ps writeFile (clusterPath opts) . unlines $ map show cl where @@ -147,5 +145,3 @@ run opts = do where tab = tabulate cl sum' f = sum . map f - - -- cgit v1.2.3