-- |
-- Module      :  ELynx.Tools.ByteString
-- Copyright   :  (c) Dominik Schrempf 2021
-- License     :  GPL-3.0-or-later
--
-- Maintainer  :  dominik.schrempf@gmail.com
-- Stability   :  unstable
-- Portability :  portable
--
-- Creation date: Thu Feb 14 13:24:53 2019.
--
-- indispensable tools for ByteString handling :).
module ELynx.Tools.ByteString
  ( -- * ByteString handling
    alignRightWith,
    alignRight,
    alignLeftWith,
    alignLeft,
  )
where

import qualified Data.ByteString.Lazy.Char8 as BL

-- | For a given width, align string to the right; use given fill character;
-- trim on the left if string is longer.
alignRightWith :: Char -> Int -> BL.ByteString -> BL.ByteString
alignRightWith :: Char -> Int -> ByteString -> ByteString
alignRightWith Char
c Int
n ByteString
s =
  Int64 -> Char -> ByteString
BL.replicate (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
l) Char
c ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int64 -> ByteString -> ByteString
BL.take (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) ByteString
s
  where
    l :: Int64
l = ByteString -> Int64
BL.length ByteString
s

-- | For a given width, align string to the right; trim on the left if string is
-- longer.
alignRight :: Int -> BL.ByteString -> BL.ByteString
alignRight :: Int -> ByteString -> ByteString
alignRight = Char -> Int -> ByteString -> ByteString
alignRightWith Char
' '

-- | For a given width, align string to the left; use given fill character; trim
-- on the right if string is longer.
alignLeftWith :: Char -> Int -> BL.ByteString -> BL.ByteString
alignLeftWith :: Char -> Int -> ByteString -> ByteString
alignLeftWith Char
c Int
n ByteString
s =
  Int64 -> ByteString -> ByteString
BL.take (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) ByteString
s ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Int64 -> Char -> ByteString
BL.replicate (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
l) Char
c
  where
    l :: Int64
l = ByteString -> Int64
BL.length ByteString
s

-- | For a given width, align string to the left; trim on the right if string is
-- longer.
alignLeft :: Int -> BL.ByteString -> BL.ByteString
alignLeft :: Int -> ByteString -> ByteString
alignLeft = Char -> Int -> ByteString -> ByteString
alignLeftWith Char
' '