| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Net.Mac
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
- 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
- print :: Mac -> IO ()
- 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) = 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
encodeWithUtf8 :: MacCodec -> Mac -> ByteString Source #
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)
decodeWithUtf8 :: MacCodec -> ByteString -> Maybe Mac Source #
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
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
| Bounded Mac Source # | |
| Enum Mac Source # | |
| Eq Mac Source # | |
| Ord Mac Source # | |
| Read Mac Source # | |
| Show Mac Source # | |
| Generic Mac Source # | |
| Hashable Mac Source # | |
| ToJSON Mac Source # | |
| ToJSONKey Mac Source # | |
| Defined in Net.Mac | |
| FromJSON Mac Source # | |
| FromJSONKey Mac Source # | |
| Defined in Net.Mac | |
| NFData 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 Methods 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 # | |
Constructors
| MacCodec | |
| Fields | |
Instances
| Eq MacCodec Source # | |
| Ord MacCodec Source # | |
| Defined in Net.Mac | |
| Read MacCodec Source # | |
| Show MacCodec Source # | |
| Generic MacCodec Source # | |
| type Rep MacCodec Source # | |
| 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,  | 
| MacGroupingTriples !Char | Three-character groups,  | 
| MacGroupingQuadruples !Char | Four-character groups,  | 
| MacGroupingNoSeparator | No separator,  |