IPv4 and IPv6 ranges.

master
Philippe Pittoli 2024-03-07 00:17:44 +01:00
parent fe3996829b
commit 0684286805
2 changed files with 38 additions and 2 deletions

View File

@ -1,7 +1,7 @@
-- | `IPAddress` is a parser for internet protocol addresses (both IPv4 and IPv6).
module GenericParser.IPAddress where
import Prelude (Ordering(..), compare, (==), (<>), (<), (+), (-), bind, pure, ($), (<<<), (>), show, map, unit)
import Prelude (Ordering(..), compare, (==), (<>), (<), (+), (-), between, bind, pure, ($), (<<<), (>), show, map, unit)
import Control.Alt ((<|>))
import Data.Array as A
@ -12,7 +12,7 @@ import GenericParser.Parser (Parser(..)
, failureError
, current_position
, string
, many1, lookahead
, read_input, many1, lookahead
, char)
import GenericParser.BaseFunctions (repeat)
import GenericParser.SomeParsers (nat)
@ -23,6 +23,7 @@ data IPv6Error
| IP6NotEnoughChunks
| IP6TooManyChunks
| IP6IrrelevantShortRepresentation
| IP6InvalidRange
-- | `ipv6_chunk` parses just a group of hexadecimal characters.
-- | Return an error (IP6TooManyHexaDecimalCharacters) in case the group has more than 4 characters.
@ -79,9 +80,22 @@ ipv6_shortened =
ipv6 :: Parser IPv6Error String
ipv6 = ipv6_shortened <|> ipv6_full
-- | `ipv6_range` parses an ipv6 range, such as "2001::1/56".
-- | If the parsing succeed, the whole string is returned.
ipv6_range :: Parser IPv6Error String
ipv6_range =
read_input do _ <- ipv6
_ <- char '/'
pos <- current_position
n <- nat
if between 0 128 n
then pure ""
else Parser \_ -> failureError pos (Just IP6InvalidRange)
data IPv4Error
= IP4NumberTooBig Int
| IP4IrrelevantShortRepresentation
| IP4InvalidRange
-- | `ipv4_byte` a parser for 0 to 255 natural integers, which is part of the representation of an IPv4 address.
ipv4_byte :: Parser IPv4Error Int
@ -127,3 +141,15 @@ ipv4_shortened =
ipv4 :: Parser IPv4Error String
ipv4 = ipv4_shortened <|> ipv4_generic4bytes
-- | `ipv4_range` parses an ipv4 range, such as "192.0.2.0/24".
-- | If the parsing succeed, the whole string is returned.
ipv4_range :: Parser IPv4Error String
ipv4_range =
read_input do _ <- ipv4
_ <- char '/'
pos <- current_position
n <- nat
if between 0 32 n
then pure ""
else Parser \_ -> failureError pos (Just IP4InvalidRange)

View File

@ -73,10 +73,12 @@ showerror_ipv6 (IP.IP6TooManyHexaDecimalCharacters) = "TooManyHexaDecimalCharact
showerror_ipv6 (IP.IP6NotEnoughChunks) = "NotEnoughChunks"
showerror_ipv6 (IP.IP6TooManyChunks) = "TooManyChunks"
showerror_ipv6 IP.IP6IrrelevantShortRepresentation = "useless double dots"
showerror_ipv6 IP.IP6InvalidRange = "invalid IPv6 range"
showerror_ipv4 :: IP.IPv4Error -> String
showerror_ipv4 (IP4NumberTooBig x) = "value '" <> show x <> "' is > 255"
showerror_ipv4 IP4IrrelevantShortRepresentation = "useless double dots"
showerror_ipv4 IP4InvalidRange = "invalid IPv4 range"
showerror_email :: EA.EmailError -> String
showerror_email EA.InvalidCharacter = "InvalidCharacter"
@ -125,3 +127,11 @@ main = do
log "Does parsers behave correctly (give the exact same input)?"
foreachE T.valid_email_addresses_short (\s -> compare_parsers "E.address" (P.read_input E.address) E.address s)
log ""
let ip4ranges = [ "10.0.0.1/24", "192.168.0.1/32", "1.2.3.4/0", "192.168.0.1/33" ]
test_series "IP.ipv4_range" IP.ipv4_range id showerror_ipv4 ip4ranges
log ""
let ip6ranges = [ "2001::1/56", "2001:1:1::1/0", "::1/128", "::1/129" ]
test_series "IP.ipv6_range" IP.ipv6_range id showerror_ipv6 ip6ranges