{-# LANGUAGE Safe #-}
{- arch-tag: Bit utilities main file
Copyright (c) 2004-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

{- |
   Module     : Data.Bits.Utils
   Copyright  : Copyright (C) 2004-2011 John Goerzen
   SPDX-License-Identifier: BSD-3-Clause

   Stability  : stable
   Portability: portable to platforms with rawSystem

  Bit-related utilities

Written by John Goerzen, jgoerzen\@complete.org
-}

module Data.Bits.Utils(getBytes, fromBytes,
                     c2w8, s2w8, w82c, w82s)
where
import           Data.Bits
import           Data.Word

{- | Returns a list representing the bytes that comprise a data type.

Example:

> getBytes (0x12345678::Int) -> [0x12, 0x34, 0x56, 0x78]
-}
getBytes :: (Integral a, Bounded a, Bits a) => a -> [a]
getBytes :: forall a. (Integral a, Bounded a, Bits a) => a -> [a]
getBytes a
input =
    let getByte :: t -> t -> [t]
getByte t
_ t
0 = []
        getByte t
x t
remaining = (t
x t -> t -> t
forall a. Bits a => a -> a -> a
.&. t
0xff) t -> [t] -> [t]
forall a. a -> [a] -> [a]
: t -> t -> [t]
getByte (t -> Int -> t
forall a. Bits a => a -> Int -> a
shiftR t
x Int
8) (t
remaining t -> t -> t
forall a. Num a => a -> a -> a
- t
1)
        in
        if (a -> Int
forall a. Bits a => a -> Int
bitSize a
input Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0
           then [Char] -> [a]
forall a. HasCallStack => [Char] -> a
error [Char]
"Input data bit size must be a multiple of 8"
           else [a] -> [a]
forall a. [a] -> [a]
reverse ([a] -> [a]) -> [a] -> [a]
forall a b. (a -> b) -> a -> b
$ a -> Int -> [a]
forall {t} {t}. (Bits t, Num t, Num t, Eq t) => t -> t -> [t]
getByte a
input (a -> Int
forall a. Bits a => a -> Int
bitSize a
input Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
8)

{- | The opposite of 'getBytes', this function builds a number based on
its component bytes.

Results are undefined if any components of the input list are > 0xff!

-}

fromBytes :: (Bits a, Num a) => [a] -> a
fromBytes :: forall a. (Bits a, Num a) => [a] -> a
fromBytes [a]
input =
    let dofb :: t -> [t] -> t
dofb t
accum []     = t
accum
        dofb t
accum (t
x:[t]
xs) = t -> [t] -> t
dofb ((t -> Int -> t
forall a. Bits a => a -> Int -> a
shiftL t
accum Int
8) t -> t -> t
forall a. Bits a => a -> a -> a
.|. t
x) [t]
xs
        in
        a -> [a] -> a
forall {t}. Bits t => t -> [t] -> t
dofb a
0 [a]
input

{- | Converts a Char to a Word8. -}
c2w8 :: Char -> Word8
c2w8 :: Char -> Word8
c2w8 = Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word8) -> (Char -> Int) -> Char -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Int
forall a. Enum a => a -> Int
fromEnum

{- | Converts a String to a [Word8]. -}
s2w8 :: String -> [Word8]
s2w8 :: [Char] -> [Word8]
s2w8 = (Char -> Word8) -> [Char] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
map Char -> Word8
c2w8

{- | Converts a Word8 to a Char. -}
w82c :: Word8 -> Char
w82c :: Word8 -> Char
w82c = Int -> Char
forall a. Enum a => Int -> a
toEnum (Int -> Char) -> (Word8 -> Int) -> Word8 -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral

{- | Converts a [Word8] to a String. -}
w82s :: [Word8] -> String
w82s :: [Word8] -> [Char]
w82s = (Word8 -> Char) -> [Word8] -> [Char]
forall a b. (a -> b) -> [a] -> [b]
map Word8 -> Char
w82c