Skip to content

Commit

Permalink
using voidHandler from ngx-export-tools 1.2.0
Browse files Browse the repository at this point in the history
  • Loading branch information
lyokha committed Oct 4, 2023
1 parent ea3d7af commit 1a05408
Show file tree
Hide file tree
Showing 10 changed files with 26 additions and 41 deletions.
8 changes: 4 additions & 4 deletions .github/workflows/ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -9,12 +9,12 @@ jobs:
continue-on-error: ${{ matrix.experimental }}
strategy:
matrix:
ghc: [8.2.2, 8.4.4, 8.6.5, 8.8.4, 8.10.7, 9.0.2, 9.2.8, 9.4.7]
cabal: [3.8.1.0]
ghc: ['8.2', '8.4', '8.6', '8.8', '8.10', '9.0', '9.2', '9.4']
cabal: ['3.8']
experimental: [false]
include:
- ghc: 9.6.3
cabal: 3.10.1.0
- ghc: '9.6'
cabal: '3.10'
experimental: false
steps:
- name: Checkout
Expand Down
11 changes: 4 additions & 7 deletions NgxExport/Tools/Aggregate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,8 +37,8 @@ module NgxExport.Tools.Aggregate (

import NgxExport
#ifdef SNAP_AGGREGATE_SERVER
import NgxExport.Tools.Combinators
import NgxExport.Tools.SimpleService
import NgxExport.Tools.SplitService
#endif
import NgxExport.Tools.System
import NgxExport.Tools.TimeInterval
Expand Down Expand Up @@ -126,21 +126,19 @@ type ReportValue a = Maybe (Int32, Maybe a)
-- {-\# NOINLINE stats \#-}
--
-- updateStats :: ByteString -> IO C8L.ByteString
-- __/updateStats/__ s = do
-- __/updateStats/__ s = voidHandler $ do
-- let cbs = 'NgxExport.Tools.Read.readFromByteString' \@Int s
-- modifyIORef\' stats $ \\(Stats bs rs _) ->
-- let !nbs = bs + fromMaybe 0 cbs
-- !nrs = rs + 1
-- !nmbs = nbs \`div\` nrs
-- in Stats nbs nrs nmbs
-- return \"\"
-- 'NgxExport.ngxExportIOYY' \'updateStats
--
-- reportStats :: Int -> Bool -> IO C8L.ByteString
-- __/reportStats/__ = 'deferredService' $ \\port -> do
-- __/reportStats/__ = 'deferredService' $ \\port -> voidHandler $ do
-- s <- readIORef stats
-- 'reportAggregate' port (Just s) \"__/stats/__\"
-- return \"\"
-- 'NgxExport.Tools.SimpleService.ngxExportSimpleServiceTyped' \'reportStats \'\'Int $
-- 'PersistentService' $ Just $ Sec 5
--
Expand Down Expand Up @@ -393,10 +391,9 @@ data AggregateServerConf =

aggregateServer :: (FromJSON a, ToJSON a) =>
Aggregate a -> ByteString -> AggregateServerConf -> Bool -> IO L.ByteString
aggregateServer a u = ignitionService $ \conf -> do
aggregateServer a u = ignitionService $ \conf -> voidHandler $ do
let !int = toNominalDiffTime $ asPurgeInterval conf
simpleHttpServe (asConfig $ asPort conf) $ asHandler a u int
return ""

asConfig :: Int -> Config Snap a
asConfig p = setPort p
Expand Down
5 changes: 2 additions & 3 deletions NgxExport/Tools/EDE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,8 @@ module NgxExport.Tools.EDE (
) where

import NgxExport
import NgxExport.Tools.Combinators
import NgxExport.Tools.SimpleService
import NgxExport.Tools.SplitService

import Text.EDE
import Text.EDE.Filters
Expand Down Expand Up @@ -225,11 +225,10 @@ templates = unsafePerformIO $ newIORef HM.empty
{-# NOINLINE templates #-}

compileEDETemplates :: InputTemplates -> Bool -> IO L.ByteString
compileEDETemplates = ignitionService $ \(path, itpls) -> do
compileEDETemplates = ignitionService $ \(path, itpls) -> voidHandler $
writeIORef templates $
foldl (\a (k, v) -> HM.insert k (unsafePerformIO $ parseIO path v) a)
HM.empty itpls
return ""

ngxExportSimpleServiceTyped 'compileEDETemplates ''InputTemplates
SingleShotService
Expand Down
13 changes: 5 additions & 8 deletions NgxExport/Tools/PCRE.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,8 +29,8 @@ module NgxExport.Tools.PCRE (
) where

import NgxExport
import NgxExport.Tools.Combinators
import NgxExport.Tools.SimpleService
import NgxExport.Tools.SplitService

import qualified Data.HashMap.Strict as HM
import Data.HashMap.Strict (HashMap)
Expand Down Expand Up @@ -160,20 +160,19 @@ regexes = unsafePerformIO $ newIORef HM.empty
{-# NOINLINE regexes #-}

declareRegexes :: InputRegexes -> Bool -> IO L.ByteString
declareRegexes = ignitionService $ const $ return ""
declareRegexes = ignitionService $ const $ voidHandler $ return ()

ngxExportSimpleServiceTyped 'declareRegexes ''InputRegexes SingleShotService

compileRegexes :: ByteString -> IO L.ByteString
compileRegexes = const $ do
compileRegexes = const $ voidHandler $ do
!inputRegexes <- fromJust <$> readIORef storage_InputRegexes_declareRegexes
let !compiledRegexes =
foldl' (\a (!k, !v, !m) -> let !r = compile v $ mods $ C8.unpack m
!hm = HM.insert k r a
in hm
) HM.empty inputRegexes
writeIORef regexes compiledRegexes
return ""
where md 'i' = Just caseless
md 's' = Just dotall
md 'm' = Just multiline
Expand All @@ -190,10 +189,8 @@ substitutions = unsafePerformIO $ newIORef HM.empty
{-# NOINLINE substitutions #-}

mapSubs :: InputSubs -> Bool -> IO L.ByteString
mapSubs = ignitionService $ \isubs -> do
writeIORef substitutions $
foldl (\a (k, v) -> HM.insert k v a) HM.empty isubs
return ""
mapSubs = ignitionService $ voidHandler .
writeIORef substitutions . foldl (\a (k, v) -> HM.insert k v a) HM.empty

ngxExportSimpleServiceTyped 'mapSubs ''InputSubs SingleShotService

Expand Down
6 changes: 2 additions & 4 deletions NgxExport/Tools/Prometheus.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,8 @@ module NgxExport.Tools.Prometheus (

import NgxExport
import NgxExport.Tools.Read
import NgxExport.Tools.Combinators
import NgxExport.Tools.SimpleService
import NgxExport.Tools.SplitService

import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
Expand Down Expand Up @@ -438,9 +438,7 @@ conf = unsafePerformIO $ newIORef Nothing
-- > hst_request_time_err 0.0

prometheusConf :: PrometheusConf -> Bool -> IO L.ByteString
prometheusConf = ignitionService $ \a -> do
writeIORef conf $ Just a
return ""
prometheusConf = ignitionService $ voidHandler . writeIORef conf . Just

ngxExportSimpleServiceTyped 'prometheusConf ''PrometheusConf SingleShotService

Expand Down
5 changes: 2 additions & 3 deletions NgxExport/Tools/Resolve.hs
Original file line number Diff line number Diff line change
Expand Up @@ -35,6 +35,7 @@ module NgxExport.Tools.Resolve (
) where

import NgxExport
import NgxExport.Tools.Combinators
import NgxExport.Tools.SimpleService
import NgxExport.Tools.TimeInterval

Expand Down Expand Up @@ -480,9 +481,7 @@ ngxExportSimpleServiceTyped 'collectUpstreams ''Conf $
type Upconf = [Text]

signalUpconf :: Upconf -> Bool -> IO L.ByteString
signalUpconf upconf = const $ do
mapConcurrently_ getUrl upconf
return ""
signalUpconf = const . voidHandler . mapConcurrently_ getUrl

ngxExportSimpleServiceTyped 'signalUpconf ''Upconf $
PersistentService Nothing
Expand Down
5 changes: 2 additions & 3 deletions NgxExport/Tools/Subrequest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,8 +47,8 @@ module NgxExport.Tools.Subrequest (

import NgxExport
import NgxExport.Tools.Read
import NgxExport.Tools.Combinators
import NgxExport.Tools.SimpleService
import NgxExport.Tools.SplitService
import NgxExport.Tools.TimeInterval

import Network.HTTP.Client hiding (ResponseTimeout)
Expand Down Expand Up @@ -476,11 +476,10 @@ ngxExportAsyncIOYY 'makeSubrequestWithRead
newtype UDSConf = UDSConf { udsPath :: FilePath } deriving Read

configureUDS :: UDSConf -> Bool -> IO L.ByteString
configureUDS = ignitionService $ \UDSConf {..} -> do
configureUDS = ignitionService $ \UDSConf {..} -> voidHandler $ do
man <- newManager defaultManagerSettings
{ managerRawConnection = return $ openUDS udsPath }
writeIORef httpUDSManager $ Just man
return ""
where openUDS path _ _ _ = do
s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
S.connect s (S.SockAddrUnix path)
Expand Down
6 changes: 2 additions & 4 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -66,21 +66,19 @@ stats = unsafePerformIO $ newIORef $ Stats 0 0 0
{-# NOINLINE stats #-}

updateStats :: ByteString -> IO C8L.ByteString
updateStats s = do
updateStats s = voidHandler $ do
let cbs = readFromByteString @Int s
modifyIORef' stats $ \(Stats bs rs _) ->
let !nbs = bs + fromMaybe 0 cbs
!nrs = rs + 1
!nmbs = nbs `div` nrs
in Stats nbs nrs nmbs
return ""
ngxExportIOYY 'updateStats

reportStats :: Int -> Bool -> IO C8L.ByteString
reportStats = deferredService $ \port -> do
reportStats = deferredService $ \port -> voidHandler $ do
s <- readIORef stats
reportAggregate port (Just s) "stats"
return ""
ngxExportSimpleServiceTyped 'reportStats ''Int $
PersistentService $ Just $ Sec 5

Expand Down
2 changes: 1 addition & 1 deletion ngx-export-tools-extra.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -40,7 +40,7 @@ library
, bytestring >= 0.10.0.0
, base64 >= 0.3.0.0
, ngx-export
, ngx-export-tools >= 1.0
, ngx-export-tools >= 1.2.0
, http-types >= 0.7.0
, http-client >= 0.5.3
, http-client-tls >= 0.3.4
Expand Down
6 changes: 2 additions & 4 deletions test/Aggregate/test_tools_extra_aggregate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -27,21 +27,19 @@ stats = unsafePerformIO $ newIORef $ Stats 0 0 0
{-# NOINLINE stats #-}

updateStats :: ByteString -> IO C8L.ByteString
updateStats s = do
updateStats s = voidHandler $ do
let cbs = readFromByteString @Int s
modifyIORef' stats $ \(Stats bs rs _) ->
let !nbs = bs + fromMaybe 0 cbs
!nrs = rs + 1
!nmbs = nbs `div` nrs
in Stats nbs nrs nmbs
return ""
ngxExportIOYY 'updateStats

reportStats :: Int -> Bool -> IO C8L.ByteString
reportStats = deferredService $ \port -> do
reportStats = deferredService $ \port -> voidHandler $ do
s <- readIORef stats
reportAggregate port (Just s) "stats"
return ""
ngxExportSimpleServiceTyped 'reportStats ''Int $
PersistentService $ Just $ Sec 5

Expand Down

0 comments on commit 1a05408

Please sign in to comment.