Skip to content

Commit

Permalink
Fix a non catched exception when an invalid prefix is given to --prefix
Browse files Browse the repository at this point in the history
  • Loading branch information
MichelBoucey committed Aug 16, 2024
1 parent d9e7a1a commit d1e2ad5
Showing 1 changed file with 32 additions and 27 deletions.
59 changes: 32 additions & 27 deletions app/ip6addr.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}

import Control.Exception
import Control.Monad (replicateM_)
import Data.Maybe
import qualified Data.Text as T (pack)
import qualified Data.Text.IO as TIO (hPutStrLn, putStrLn)
import Data.Version (showVersion)
Expand All @@ -11,27 +14,6 @@ import System.Exit
import System.IO (stderr)
import Text.IPv6Addr

data Output
= Canonical
| NoIPv4
| FullLength
| PTR
| UNC
| Random
deriving (Eq)

data Options =
Options
{ showver :: !Bool
, output :: !Output
, quantity :: !Int
, prefix :: !String
, address :: !String
}

showVer :: String
showVer = "ip6addr v" <> showVersion version <> " (c) Michel Boucey 2011-2024"

main :: IO ()
main = do
Options{..} <- execParser opts
Expand All @@ -47,10 +29,12 @@ main = do
Random -> replicateM_ quantity (putRandAddr prefix) >> exitSuccess
where
putRandAddr p = do
r <- randIPv6AddrWithPrefix (if p == mempty then Nothing else Just (T.pack p))
case r of
Just a -> TIO.putStrLn (unIPv6Addr a)
Nothing -> TIO.putStrLn "Bad prefix"
let p' = T.pack p
t <- try $ randIPv6AddrWithPrefix (if p == mempty then Nothing else Just p')
case t of
Right a -> TIO.putStrLn (unIPv6Addr $ fromJust a)
Left (_ :: SomeException) ->
TIO.putStrLn (p' <> " is an invalid prefix") >> exitFailure
out t i o =
if i /= mempty
then do
Expand All @@ -63,6 +47,27 @@ main = do
maybeUNC t = toUNC <$> maybePureIPv6Addr t
maybeIP6ARPA t = toIP6ARPA <$> maybeFullIPv6Addr t

showVer :: String
showVer = "ip6addr v" <> showVersion version <> " (c) Michel Boucey 2011-2024"

data Output
= Canonical
| NoIPv4
| FullLength
| PTR
| UNC
| Random
deriving (Eq)

data Options =
Options
{ showver :: !Bool
, output :: !Output
, quantity :: !Int
, prefix :: !String
, address :: !String
}

opts :: ParserInfo Options
opts = info (parseOptions <**> helper)
( fullDesc
Expand Down

0 comments on commit d1e2ad5

Please sign in to comment.