{-# LANGUAGE UndecidableInstances #-}
module Data.Bytes.Formatting.Size
( SizeFormat (..),
_SizeFormatShort,
_SizeFormatMedium,
_SizeFormatLong,
SizedFormatter (..),
formatSize,
sizedFormatterUnix,
sizedFormatterNatural,
sizedFormatterVerbose,
)
where
import Data.Bytes.Formatting.Base
( CaseFormat
( CaseFormatLower,
CaseFormatUpper
),
Formatter (formatStr),
caseFormatToFn,
)
import Data.Bytes.Size (Size (B, E, G, K, M, P, T, Y, Z), Sized (sizeOf))
import Data.Default (Default (def))
import Data.Text (Text)
import Data.Text qualified as T
import Optics.Core
( A_Lens,
LabelOptic (labelOptic),
Prism',
lens,
prism,
(^.),
)
import Text.Printf (printf)
data SizeFormat
=
SizeFormatShort
|
SizeFormatMedium
|
SizeFormatLong
deriving stock
(
SizeFormat -> SizeFormat -> Bool
(SizeFormat -> SizeFormat -> Bool)
-> (SizeFormat -> SizeFormat -> Bool) -> Eq SizeFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SizeFormat -> SizeFormat -> Bool
== :: SizeFormat -> SizeFormat -> Bool
$c/= :: SizeFormat -> SizeFormat -> Bool
/= :: SizeFormat -> SizeFormat -> Bool
Eq,
Int -> SizeFormat -> ShowS
[SizeFormat] -> ShowS
SizeFormat -> String
(Int -> SizeFormat -> ShowS)
-> (SizeFormat -> String)
-> ([SizeFormat] -> ShowS)
-> Show SizeFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SizeFormat -> ShowS
showsPrec :: Int -> SizeFormat -> ShowS
$cshow :: SizeFormat -> String
show :: SizeFormat -> String
$cshowList :: [SizeFormat] -> ShowS
showList :: [SizeFormat] -> ShowS
Show
)
instance Default SizeFormat where
def :: SizeFormat
def = SizeFormat
SizeFormatMedium
_SizeFormatShort :: Prism' SizeFormat ()
_SizeFormatShort :: Prism' SizeFormat ()
_SizeFormatShort = (() -> SizeFormat)
-> (SizeFormat -> Either SizeFormat ()) -> Prism' SizeFormat ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (SizeFormat -> () -> SizeFormat
forall a b. a -> b -> a
const SizeFormat
SizeFormatShort) SizeFormat -> Either SizeFormat ()
f
where
f :: SizeFormat -> Either SizeFormat ()
f SizeFormat
SizeFormatShort = () -> Either SizeFormat ()
forall a b. b -> Either a b
Right ()
f SizeFormat
other = SizeFormat -> Either SizeFormat ()
forall a b. a -> Either a b
Left SizeFormat
other
_SizeFormatMedium :: Prism' SizeFormat ()
_SizeFormatMedium :: Prism' SizeFormat ()
_SizeFormatMedium = (() -> SizeFormat)
-> (SizeFormat -> Either SizeFormat ()) -> Prism' SizeFormat ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (SizeFormat -> () -> SizeFormat
forall a b. a -> b -> a
const SizeFormat
SizeFormatMedium) SizeFormat -> Either SizeFormat ()
f
where
f :: SizeFormat -> Either SizeFormat ()
f SizeFormat
SizeFormatMedium = () -> Either SizeFormat ()
forall a b. b -> Either a b
Right ()
f SizeFormat
other = SizeFormat -> Either SizeFormat ()
forall a b. a -> Either a b
Left SizeFormat
other
_SizeFormatLong :: Prism' SizeFormat ()
_SizeFormatLong :: Prism' SizeFormat ()
_SizeFormatLong = (() -> SizeFormat)
-> (SizeFormat -> Either SizeFormat ()) -> Prism' SizeFormat ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (SizeFormat -> () -> SizeFormat
forall a b. a -> b -> a
const SizeFormat
SizeFormatLong) SizeFormat -> Either SizeFormat ()
f
where
f :: SizeFormat -> Either SizeFormat ()
f SizeFormat
SizeFormatLong = () -> Either SizeFormat ()
forall a b. b -> Either a b
Right ()
f SizeFormat
other = SizeFormat -> Either SizeFormat ()
forall a b. a -> Either a b
Left SizeFormat
other
data SizedFormatter = MkSizedFormatter
{ SizedFormatter -> CaseFormat
caseFormat :: CaseFormat,
SizedFormatter -> Bool
leadingSpace :: Bool,
SizedFormatter -> SizeFormat
sizeFormat :: SizeFormat
}
deriving stock
(
SizedFormatter -> SizedFormatter -> Bool
(SizedFormatter -> SizedFormatter -> Bool)
-> (SizedFormatter -> SizedFormatter -> Bool) -> Eq SizedFormatter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SizedFormatter -> SizedFormatter -> Bool
== :: SizedFormatter -> SizedFormatter -> Bool
$c/= :: SizedFormatter -> SizedFormatter -> Bool
/= :: SizedFormatter -> SizedFormatter -> Bool
Eq,
Int -> SizedFormatter -> ShowS
[SizedFormatter] -> ShowS
SizedFormatter -> String
(Int -> SizedFormatter -> ShowS)
-> (SizedFormatter -> String)
-> ([SizedFormatter] -> ShowS)
-> Show SizedFormatter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SizedFormatter -> ShowS
showsPrec :: Int -> SizedFormatter -> ShowS
$cshow :: SizedFormatter -> String
show :: SizedFormatter -> String
$cshowList :: [SizedFormatter] -> ShowS
showList :: [SizedFormatter] -> ShowS
Show
)
instance Default SizedFormatter where
def :: SizedFormatter
def = CaseFormat -> Bool -> SizeFormat -> SizedFormatter
MkSizedFormatter CaseFormat
CaseFormatLower Bool
True SizeFormat
forall a. Default a => a
def
instance
(k ~ A_Lens, a ~ CaseFormat, b ~ CaseFormat) =>
LabelOptic "caseFormat" k SizedFormatter SizedFormatter a b
where
labelOptic :: Optic k NoIx SizedFormatter SizedFormatter a b
labelOptic = (SizedFormatter -> a)
-> (SizedFormatter -> b -> SizedFormatter)
-> Lens SizedFormatter SizedFormatter a b
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens SizedFormatter -> a
SizedFormatter -> CaseFormat
caseFormat (\SizedFormatter
f b
cf -> SizedFormatter
f {caseFormat = cf})
instance
(k ~ A_Lens, a ~ Bool, b ~ Bool) =>
LabelOptic "leadingSpace" k SizedFormatter SizedFormatter a b
where
labelOptic :: Optic k NoIx SizedFormatter SizedFormatter a b
labelOptic = (SizedFormatter -> a)
-> (SizedFormatter -> b -> SizedFormatter)
-> Lens SizedFormatter SizedFormatter a b
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens SizedFormatter -> a
SizedFormatter -> Bool
leadingSpace (\SizedFormatter
f b
ls -> SizedFormatter
f {leadingSpace = ls})
instance
(k ~ A_Lens, a ~ SizeFormat, b ~ SizeFormat) =>
LabelOptic "sizeFormat" k SizedFormatter SizedFormatter a b
where
labelOptic :: Optic k NoIx SizedFormatter SizedFormatter a b
labelOptic = (SizedFormatter -> a)
-> (SizedFormatter -> b -> SizedFormatter)
-> Lens SizedFormatter SizedFormatter a b
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens SizedFormatter -> a
SizedFormatter -> SizeFormat
sizeFormat (\SizedFormatter
f b
sf -> SizedFormatter
f {sizeFormat = sf})
instance Formatter SizedFormatter where
formatStr :: SizedFormatter -> Text
formatStr SizedFormatter
fmt =
if SizedFormatter
fmt SizedFormatter -> Optic' A_Lens NoIx SizedFormatter Bool -> Bool
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SizedFormatter Bool
#leadingSpace
then Text
" %s"
else Text
"%s"
sizedFormatterUnix :: SizedFormatter
sizedFormatterUnix :: SizedFormatter
sizedFormatterUnix = CaseFormat -> Bool -> SizeFormat -> SizedFormatter
MkSizedFormatter CaseFormat
CaseFormatUpper Bool
False SizeFormat
SizeFormatShort
sizedFormatterNatural :: SizedFormatter
sizedFormatterNatural :: SizedFormatter
sizedFormatterNatural = CaseFormat -> Bool -> SizeFormat -> SizedFormatter
MkSizedFormatter CaseFormat
CaseFormatLower Bool
True SizeFormat
SizeFormatMedium
sizedFormatterVerbose :: SizedFormatter
sizedFormatterVerbose :: SizedFormatter
sizedFormatterVerbose = CaseFormat -> Bool -> SizeFormat -> SizedFormatter
MkSizedFormatter CaseFormat
CaseFormatLower Bool
True SizeFormat
SizeFormatLong
formatSize :: (Sized a) => SizedFormatter -> a -> Text
formatSize :: forall a. Sized a => SizedFormatter -> a -> Text
formatSize SizedFormatter
fmt a
x = String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String -> Text -> String
forall r. PrintfType r => String -> r
printf (Text -> String
T.unpack (Text -> String) -> Text -> String
forall a b. (a -> b) -> a -> b
$ SizedFormatter -> Text
forall a. Formatter a => a -> Text
formatStr SizedFormatter
fmt) Text
size'
where
size :: Text
size = SizeFormat -> Size -> Text
formatSize' (SizedFormatter
fmt SizedFormatter
-> Optic' A_Lens NoIx SizedFormatter SizeFormat -> SizeFormat
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SizedFormatter SizeFormat
#sizeFormat) (a -> Size
forall a. Sized a => a -> Size
sizeOf a
x)
size' :: Text
size' = CaseFormat -> Text -> Text
caseFormatToFn (SizedFormatter
fmt SizedFormatter
-> Optic' A_Lens NoIx SizedFormatter CaseFormat -> CaseFormat
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx SizedFormatter CaseFormat
#caseFormat) Text
size
formatSize' :: SizeFormat -> Size -> Text
formatSize' :: SizeFormat -> Size -> Text
formatSize' SizeFormat
SizeFormatShort = Size -> Text
formatSizeShort
formatSize' SizeFormat
SizeFormatMedium = Size -> Text
formatSizeMedium
formatSize' SizeFormat
SizeFormatLong = Size -> Text
formatSizeLong
formatSizeShort :: Size -> Text
formatSizeShort :: Size -> Text
formatSizeShort Size
B = Text
"B"
formatSizeShort Size
K = Text
"K"
formatSizeShort Size
M = Text
"M"
formatSizeShort Size
G = Text
"G"
formatSizeShort Size
T = Text
"T"
formatSizeShort Size
P = Text
"P"
formatSizeShort Size
E = Text
"E"
formatSizeShort Size
Z = Text
"Z"
formatSizeShort Size
Y = Text
"Y"
formatSizeMedium :: Size -> Text
formatSizeMedium :: Size -> Text
formatSizeMedium Size
B = Text
"B"
formatSizeMedium Size
K = Text
"KB"
formatSizeMedium Size
M = Text
"MB"
formatSizeMedium Size
G = Text
"GB"
formatSizeMedium Size
T = Text
"TB"
formatSizeMedium Size
P = Text
"PB"
formatSizeMedium Size
E = Text
"EB"
formatSizeMedium Size
Z = Text
"ZB"
formatSizeMedium Size
Y = Text
"YB"
formatSizeLong :: Size -> Text
formatSizeLong :: Size -> Text
formatSizeLong Size
B = Text
"Bytes"
formatSizeLong Size
K = Text
"Kilobytes"
formatSizeLong Size
M = Text
"Megabytes"
formatSizeLong Size
G = Text
"Gigabytes"
formatSizeLong Size
T = Text
"Terabytes"
formatSizeLong Size
P = Text
"Petabytes"
formatSizeLong Size
E = Text
"Exabytes"
formatSizeLong Size
Z = Text
"Zettabytes"
formatSizeLong Size
Y = Text
"Yottabytes"