Accept simplistic IPv6 representations.

master
Philippe Pittoli 2024-01-23 04:46:08 +01:00
parent c441dc0477
commit ef1a0e40a3
2 changed files with 53 additions and 4 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 (bind, pure, ($), (<<<), (>), show, map)
import Prelude (between, (||), bind, pure, ($), (<<<), (>), show, map)
-- import Control.Alt ((<|>))
-- import Control.Lazy (defer)
@ -9,12 +9,45 @@ import Data.Array as A
-- import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
-- import Data.String as S
-- import Data.String.CodeUnits as CU
import Data.String.CodeUnits as CU
import GenericParser.Parser (Parser(..)
, failureError
, current_position
, char, nat, eof)
, tryMaybe
, many1
, sat, char, nat)
data IPv6Error
= InvalidCharacter
| TooManyHexaDecimalCharacters
isHexaDecimal :: Char -> Boolean
isHexaDecimal c = between '0' '9' c || between 'a' 'f' c || between 'A' 'F' c
hex :: forall e. Parser e Char
hex = sat isHexaDecimal
-- | `ipv6_chunk` analyses just a nibble
ipv6_chunk :: Parser IPv6Error String
ipv6_chunk = do pos <- current_position
hexachars <- many1 hex
_ <- tryMaybe $ char ':'
if A.length hexachars > 4
then Parser \_ -> failureError pos (Just TooManyHexaDecimalCharacters)
else pure $ CU.fromCharArray hexachars
-- | TODO: `ipv6` currently is oversimplistic and lacks shortened representation (with doubled ':' character).
-- |
-- | TODO: check for double ':'
-- |
-- | TODO: verify the number of chunks (groups of hexadecimal characters).
-- |
-- | TODO: accept IPv6 addresses between brackets ([ipv6]).
ipv6 :: Parser IPv6Error String
ipv6 = do chunks <- many1 ipv6_chunk
pure $ A.fold (A.intersperse ":" chunks)
data IPv4Error
= NumberTooBig Int
@ -35,7 +68,6 @@ ipv4_generic4bytes =
b3 <- ipv4_byte
_ <- char '.'
b4 <- ipv4_byte
_ <- eof
pure $ A.fold (A.intersperse "." $ map show [b1,b2,b3,b4])
ipv4 :: Parser IPv4Error String

View File

@ -41,6 +41,19 @@ test_series :: forall e v
-> Effect Unit
test_series l p v e a = foreachE a (\s -> logtest l p s v e)
showerror_ipv6 :: IP.IPv6Error -> String
showerror_ipv6 (IP.InvalidCharacter) = "InvalidCharacter"
showerror_ipv6 (IP.TooManyHexaDecimalCharacters) = "TooManyHexaDecimalCharacters"
test_ipv6 :: String -> Effect Unit
test_ipv6 ipv6string = do
log $ "(ipv6) parsing '" <> ipv6string <> "': "
<> case parse IP.ipv6 { string: ipv6string, position: 0 } of
Left { position, error } -> "failed at position " <> show position <> case error of
Nothing -> " -> no error reported"
Just err -> " -> error: " <> showerror_ipv6 err
Right { suffix, result } -> "result: " <> result <> " '" <> suffix.string <> "'"
showerror_ipv4 :: IP.IPv4Error -> String
showerror_ipv4 (NumberTooBig x) = "value '" <> show x <> "' is > 255"
@ -87,3 +100,7 @@ main = do
test_ipv4 "1..2.3.4"
test_ipv4 "1.5.10.255"
test_ipv4 "100.200.300.400"
log ""
test_ipv6 "2001:0"
test_ipv6 "2001:0db8:0000:0000:0000:8a2e:0370:7334"