ip-1.4.1: Library for IP and MAC addresses

Safe HaskellNone
LanguageHaskell2010

Net.Mac

Contents

Synopsis

Convert

mac :: Word64 -> Mac Source #

Construct a Mac address from a Word64. Only the lower 48 bits are used.

fromOctets :: Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Mac Source #

Create a Mac address from six octets.

toOctets :: Mac -> (Word8, Word8, Word8, Word8, Word8, Word8) Source #

Convert a Mac address to the six octets that make it up. This function and fromOctets are inverses:

m == (let (a,b,c,d,e,f) = toOctets m in fromOctets a b c d e f)

Textual Conversion

Text

encode :: Mac -> Text Source #

Encode a Mac address lowercase hex, separating every two characters with a colon:

>>> T.putStrLn (encode (Mac 0xA47F247AB423))
a4:7f:24:7a:b4:23

UTF-8 ByteString

encodeUtf8 :: Mac -> ByteString Source #

Encode a Mac address, as lowercase hexadecimal digits separated by a colon:

>>> BC.putStrLn (encodeUtf8 (mac 0x64255A0F2C47))
64:25:5a:0f:2c:47

decodeUtf8 :: ByteString -> Maybe Mac Source #

Lenient decoding of MAC address that accepts lowercase, uppercase, and any kind separator.

>>> decodeUtf8 "A2:DE:AD:BE:EF:67"
Just (mac 0xa2deadbeef67)
>>> decodeUtf8 "13-a2-fe-a4-17-96"
Just (mac 0x13a2fea41796)
>>> decodeUtf8 "0A42.47BA.67C2"
Just (mac 0x0a4247ba67c2)

builderUtf8 :: Mac -> Builder Source #

Make a bytestring builder from a Mac address using a colon as the separator.

parserUtf8 :: Parser Mac Source #

Lenient parser for a Mac address using any character as the separator and accepting any digit grouping (i.e. FA:43:B2:C0:0F:99 or A065.647B.87FA).

parserWithUtf8 :: MacCodec -> Parser Mac Source #

Parser for a Mac address using the provided settings.

ByteString

decodeBytes :: ByteString -> Maybe Mac Source #

Decode a Mac address from a ByteString. Each byte is interpreted as an octet of the Mac address. Consequently, ByteStrings of length 6 successfully decode, and all other ByteStrings fail to decode.

>>> decodeBytes (B.pack [0x6B,0x47,0x18,0x90,0x55,0xC3])
Just (mac 0x6b47189055c3)
>>> decodeBytes (B.replicate 6 0x3A)
Just (mac 0x3a3a3a3a3a3a)
>>> decodeBytes (B.replicate 7 0x3A)
Nothing

Printing

print :: Mac -> IO () Source #

Types

newtype Mac Source #

A 48-bit MAC address. Do not use the data constructor for this type. It is not considered part of the stable API, and it allows you to construct invalid MAC addresses.

Constructors

Mac Word64 
Instances
Bounded Mac Source # 
Instance details

Defined in Net.Mac

Methods

minBound :: Mac #

maxBound :: Mac #

Enum Mac Source # 
Instance details

Defined in Net.Mac

Methods

succ :: Mac -> Mac #

pred :: Mac -> Mac #

toEnum :: Int -> Mac #

fromEnum :: Mac -> Int #

enumFrom :: Mac -> [Mac] #

enumFromThen :: Mac -> Mac -> [Mac] #

enumFromTo :: Mac -> Mac -> [Mac] #

enumFromThenTo :: Mac -> Mac -> Mac -> [Mac] #

Eq Mac Source # 
Instance details

Defined in Net.Mac

Methods

(==) :: Mac -> Mac -> Bool #

(/=) :: Mac -> Mac -> Bool #

Ord Mac Source # 
Instance details

Defined in Net.Mac

Methods

compare :: Mac -> Mac -> Ordering #

(<) :: Mac -> Mac -> Bool #

(<=) :: Mac -> Mac -> Bool #

(>) :: Mac -> Mac -> Bool #

(>=) :: Mac -> Mac -> Bool #

max :: Mac -> Mac -> Mac #

min :: Mac -> Mac -> Mac #

Read Mac Source # 
Instance details

Defined in Net.Mac

Show Mac Source # 
Instance details

Defined in Net.Mac

Methods

showsPrec :: Int -> Mac -> ShowS #

show :: Mac -> String #

showList :: [Mac] -> ShowS #

Generic Mac Source # 
Instance details

Defined in Net.Mac

Associated Types

type Rep Mac :: * -> * #

Methods

from :: Mac -> Rep Mac x #

to :: Rep Mac x -> Mac #

Hashable Mac Source # 
Instance details

Defined in Net.Mac

Methods

hashWithSalt :: Int -> Mac -> Int #

hash :: Mac -> Int #

ToJSON Mac Source # 
Instance details

Defined in Net.Mac

ToJSONKey Mac Source # 
Instance details

Defined in Net.Mac

FromJSON Mac Source # 
Instance details

Defined in Net.Mac

FromJSONKey Mac Source # 
Instance details

Defined in Net.Mac

NFData Mac Source # 
Instance details

Defined in Net.Mac

Methods

rnf :: Mac -> () #

Prim Mac Source #

This only preserves the lower 6 bytes of the 8-byte word that backs a mac address. It runs slower than it would if it used a full 8-byte word, but it consumes less space. When storing millions of mac addresses, this is a good trade to make. When storing a small number of mac address, it might be preferable to make a primitive array of Word64 instead and use the mac address data constructor to coerce between the two.

Instance details

Defined in Net.Mac

type Rep Mac Source # 
Instance details

Defined in Net.Mac

type Rep Mac = D1 (MetaData "Mac" "Net.Mac" "ip-1.4.1-EoFLganEe87B23MDW12YOQ" True) (C1 (MetaCons "Mac" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))

data MacCodec Source #

Instances
Eq MacCodec Source # 
Instance details

Defined in Net.Mac

Ord MacCodec Source # 
Instance details

Defined in Net.Mac

Read MacCodec Source # 
Instance details

Defined in Net.Mac

Show MacCodec Source # 
Instance details

Defined in Net.Mac

Generic MacCodec Source # 
Instance details

Defined in Net.Mac

Associated Types

type Rep MacCodec :: * -> * #

Methods

from :: MacCodec -> Rep MacCodec x #

to :: Rep MacCodec x -> MacCodec #

type Rep MacCodec Source # 
Instance details

Defined in Net.Mac

type Rep MacCodec = D1 (MetaData "MacCodec" "Net.Mac" "ip-1.4.1-EoFLganEe87B23MDW12YOQ" False) (C1 (MetaCons "MacCodec" PrefixI True) (S1 (MetaSel (Just "macCodecGrouping") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MacGrouping) :*: S1 (MetaSel (Just "macCodecUpperCase") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)))

data MacGrouping Source #

The format expected by the mac address parser. The Word8 taken by some of these constructors is the ascii value of the character to be used as the separator. This is typically a colon, a hyphen, or a space character. All decoding functions are case insensitive.

Constructors

MacGroupingPairs !Char

Two-character groups, FA:2B:40:09:8C:11

MacGroupingTriples !Char

Three-character groups, 24B-F0A-025-829

MacGroupingQuadruples !Char

Four-character groups, A220.0745.CAC7

MacGroupingNoSeparator

No separator, 24AF4B5B0780

Instances
Eq MacGrouping Source # 
Instance details

Defined in Net.Mac

Ord MacGrouping Source # 
Instance details

Defined in Net.Mac

Read MacGrouping Source # 
Instance details

Defined in Net.Mac

Show MacGrouping Source # 
Instance details

Defined in Net.Mac

Generic MacGrouping Source # 
Instance details

Defined in Net.Mac

Associated Types

type Rep MacGrouping :: * -> * #

type Rep MacGrouping Source # 
Instance details

Defined in Net.Mac

type Rep MacGrouping = D1 (MetaData "MacGrouping" "Net.Mac" "ip-1.4.1-EoFLganEe87B23MDW12YOQ" False) ((C1 (MetaCons "MacGroupingPairs" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char)) :+: C1 (MetaCons "MacGroupingTriples" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char))) :+: (C1 (MetaCons "MacGroupingQuadruples" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char)) :+: C1 (MetaCons "MacGroupingNoSeparator" PrefixI False) (U1 :: * -> *)))