Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides the Mac data type and functions for working with it.
Synopsis
- mac :: Word64 -> Mac
- fromOctets :: Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Word8 -> Mac
- toOctets :: Mac -> (Word8, Word8, Word8, Word8, Word8, Word8)
- encode :: Mac -> Text
- encodeWith :: MacCodec -> Mac -> Text
- decode :: Text -> Maybe Mac
- decodeWith :: MacCodec -> Text -> Maybe Mac
- builder :: Mac -> Builder
- parser :: Parser Mac
- parserWith :: MacCodec -> Parser Mac
- encodeShort :: Mac -> ShortText
- encodeUtf8 :: Mac -> ByteString
- encodeWithUtf8 :: MacCodec -> Mac -> ByteString
- decodeUtf8 :: ByteString -> Maybe Mac
- decodeWithUtf8 :: MacCodec -> ByteString -> Maybe Mac
- builderUtf8 :: Mac -> Builder
- parserUtf8 :: Parser Mac
- parserWithUtf8 :: MacCodec -> Parser Mac
- decodeBytes :: ByteString -> Maybe Mac
- decodeOctets :: ByteString -> Maybe Mac
- boundedBuilderUtf8 :: Mac -> Builder 17
- decodeUtf8Bytes :: Bytes -> Maybe Mac
- parserUtf8Bytes :: e -> Parser e s Mac
- print :: Mac -> IO ()
- defCodec :: MacCodec
- newtype Mac = Mac Word64
- data MacCodec = MacCodec {}
- data MacGrouping
Convert
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) = Mac.toOctets m in Mac.fromOctets a b c d e f)
Textual Conversion
Text
parserWith :: MacCodec -> Parser Mac Source #
Parser a Mac
address using the given MacCodec
.
>>>
p1 = Mac.parserWith Mac.defCodec
>>>
AT.parseOnly p1 (Text.pack "a4:7f:24:7a:b4:23")
Right (mac 0xa47f247ab423)
>>>
p2 = Mac.parserWith (Mac.MacCodec Mac.MacGroupingNoSeparator False)
>>>
AT.parseOnly p2 (Text.pack "a47f247ab423")
Right (mac 0xa47f247ab423)
ShortText
encodeShort :: Mac -> ShortText Source #
Encode a Mac
address as colon-separated hexadecimal octets,
preferring lowercase for alphabetical characters.
UTF-8 ByteString
encodeUtf8 :: Mac -> ByteString Source #
encodeWithUtf8 :: MacCodec -> Mac -> ByteString Source #
Encode a Mac
address as a ByteString
using the given MacCodec
.
>>>
m = Mac 0xA47F247AB423
>>>
BC.putStrLn $ Mac.encodeWithUtf8 Mac.defCodec m
a4:7f:24:7a:b4:23
>>>
BC.putStrLn $ Mac.encodeWithUtf8 (Mac.MacCodec (Mac.MacGroupingTriples '-') True) m
A47-F24-7AB-423
decodeUtf8 :: ByteString -> Maybe Mac Source #
Lenient decoding of MAC address that accepts lowercase, uppercase, and any kind of separator.
>>>
Mac.decodeUtf8 "A2:DE:AD:BE:EF:67"
Just (mac 0xa2deadbeef67)>>>
Mac.decodeUtf8 "13-a2-fe-a4-17-96"
Just (mac 0x13a2fea41796)>>>
Mac.decodeUtf8 "0A42.47BA.67C2"
Just (mac 0x0a4247ba67c2)
decodeWithUtf8 :: MacCodec -> ByteString -> Maybe Mac Source #
Decode a ByteString
as a Mac
address using the given MacCodec
.
>>>
Mac.decodeWithUtf8 Mac.defCodec (BC.pack "64:25:5a:0f:2c:47")
Just (mac 0x64255a0f2c47)
>>>
Mac.decodeWithUtf8 (Mac.MacCodec Mac.MacGroupingNoSeparator False) (BC.pack "64255a0f2c47")
Just (mac 0x64255a0f2c47)
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 #
Deprecated: Prefer decodeOctets
This function is deprecated. It will be renamed in a future release since the name is misleading.
decodeOctets :: ByteString -> Maybe Mac Source #
Decode a Mac
address from a ByteString
. Each byte is interpreted
as an octet of the Mac
address. Consequently, ByteString
s
of length 6 successfully decode, and all other ByteString
s fail
to decode.
>>>
Mac.decodeOctets (B.pack [0x6B,0x47,0x18,0x90,0x55,0xC3])
Just (mac 0x6b47189055c3)>>>
Mac.decodeOctets (B.replicate 6 0x3A)
Just (mac 0x3a3a3a3a3a3a)>>>
Mac.decodeOctets (B.replicate 7 0x3A)
Nothing
Note that the octets are interpreted in a big-endian fashion.
UTF-8 Bytes
boundedBuilderUtf8 :: Mac -> Builder 17 Source #
Encode a Mac
address as colon-separated hexadecimal octets,
preferring lowercase for alphabetical characters.
>>>
BBB.run Nat.constant $ Mac.boundedBuilderUtf8 $ Mac.mac 0xDEADBEEF1609
[0x64, 0x65, 0x3a, 0x61, 0x64, 0x3a, 0x62, 0x65, 0x3a, 0x65, 0x66, 0x3a, 0x31, 0x36, 0x3a, 0x30, 0x39]
decodeUtf8Bytes :: Bytes -> Maybe Mac Source #
Lenient decoding of MAC address. This
is case insensitive and allows either :
or -
as the separator.
It also allows leading zeroes to be missing.
>>>
Mac.decodeUtf8Bytes (Ascii.fromString "A2:DE:AD:BE:EF:67")
Just (mac 0xa2deadbeef67)>>>
Mac.decodeUtf8Bytes (Ascii.fromString "13-a2-FE-A4-17-96")
Just (mac 0x13a2fea41796)
parserUtf8Bytes :: e -> Parser e s Mac Source #
Leniently parse UTF-8-encoded Bytes
as a Mac
address. This
is case insensitive and allows either :
or -
as the separator.
It also allows leading zeroes to be missing.
>>>
Parser.parseBytes (Mac.parserUtf8Bytes ()) (Ascii.fromString "de:ad:BE:EF:1:23")
Success (Slice {offset = 16, length = 0, value = mac 0xdeadbeef0123})
Printing
Default Codec
The default MacCodec
: all characters are lowercase hex, separated by colons into pairs.
>>>
T.putStrLn $ Mac.encodeWith Mac.defCodec (Mac 0xa47f247ab423)
a4:7f:24:7a:b4:23
Types
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.
Instances
FromJSON Mac Source # | |
FromJSONKey Mac Source # | |
Defined in Net.Mac | |
ToJSON Mac Source # | |
ToJSONKey Mac Source # | |
Defined in Net.Mac | |
Data Mac Source # | |
Defined in Net.Mac gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Mac -> c Mac # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Mac # dataTypeOf :: Mac -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Mac) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Mac) # gmapT :: (forall b. Data b => b -> b) -> Mac -> Mac # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Mac -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Mac -> r # gmapQ :: (forall d. Data d => d -> u) -> Mac -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Mac -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Mac -> m Mac # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Mac -> m Mac # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Mac -> m Mac # | |
Bounded Mac Source # | |
Enum Mac Source # | |
Generic Mac Source # | |
Ix Mac Source # | |
Read Mac Source # | |
Show Mac Source # | |
NFData Mac Source # | |
Eq Mac Source # | |
Ord Mac Source # | |
Hashable Mac Source # | |
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 |
Defined in Net.Mac sizeOfType# :: Proxy Mac -> Int# # alignmentOfType# :: Proxy Mac -> Int# # alignment# :: Mac -> Int# # indexByteArray# :: ByteArray# -> Int# -> Mac # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Mac #) # writeByteArray# :: MutableByteArray# s -> Int# -> Mac -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Mac -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Mac # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Mac #) # writeOffAddr# :: Addr# -> Int# -> Mac -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Mac -> State# s -> State# s # | |
type Rep Mac Source # | |
Instances
Data MacCodec Source # | |
Defined in Net.Mac gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MacCodec -> c MacCodec # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MacCodec # toConstr :: MacCodec -> Constr # dataTypeOf :: MacCodec -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MacCodec) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MacCodec) # gmapT :: (forall b. Data b => b -> b) -> MacCodec -> MacCodec # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MacCodec -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MacCodec -> r # gmapQ :: (forall d. Data d => d -> u) -> MacCodec -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MacCodec -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MacCodec -> m MacCodec # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MacCodec -> m MacCodec # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MacCodec -> m MacCodec # | |
Generic MacCodec Source # | |
Read MacCodec Source # | |
Show MacCodec Source # | |
Eq MacCodec Source # | |
Ord MacCodec Source # | |
type Rep MacCodec Source # | |
Defined in Net.Mac type Rep MacCodec = D1 ('MetaData "MacCodec" "Net.Mac" "ip-1.7.8-LlpdK7rg6it5d78V5ukAkK" '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.
MacGroupingPairs !Char | Two-character groups, |
MacGroupingTriples !Char | Three-character groups, |
MacGroupingQuadruples !Char | Four-character groups, |
MacGroupingNoSeparator | No separator, |