{-# LANGUAGE UndecidableInstances #-}
module Data.Bytes.Formatting.Direction
( DirectionFormat (..),
_DirectionFormatShort,
_DirectionFormatLong,
DirectedFormatter (..),
formatDirection,
directedFormatterUnix,
directedFormatterVerbose,
)
where
import Data.Bytes.Formatting.Base
( CaseFormat
( CaseFormatLower,
CaseFormatUpper
),
Formatter (formatStr),
caseFormatToFn,
)
import Data.Bytes.Network.Direction
( Directed (directionOf),
Direction (Down, Up),
)
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 DirectionFormat
=
DirectionFormatShort
|
DirectionFormatLong
deriving stock
(
DirectionFormat -> DirectionFormat -> Bool
(DirectionFormat -> DirectionFormat -> Bool)
-> (DirectionFormat -> DirectionFormat -> Bool)
-> Eq DirectionFormat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirectionFormat -> DirectionFormat -> Bool
== :: DirectionFormat -> DirectionFormat -> Bool
$c/= :: DirectionFormat -> DirectionFormat -> Bool
/= :: DirectionFormat -> DirectionFormat -> Bool
Eq,
Int -> DirectionFormat -> ShowS
[DirectionFormat] -> ShowS
DirectionFormat -> String
(Int -> DirectionFormat -> ShowS)
-> (DirectionFormat -> String)
-> ([DirectionFormat] -> ShowS)
-> Show DirectionFormat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DirectionFormat -> ShowS
showsPrec :: Int -> DirectionFormat -> ShowS
$cshow :: DirectionFormat -> String
show :: DirectionFormat -> String
$cshowList :: [DirectionFormat] -> ShowS
showList :: [DirectionFormat] -> ShowS
Show
)
instance Default DirectionFormat where
def :: DirectionFormat
def = DirectionFormat
DirectionFormatLong
_DirectionFormatShort :: Prism' DirectionFormat ()
_DirectionFormatShort :: Prism' DirectionFormat ()
_DirectionFormatShort = (() -> DirectionFormat)
-> (DirectionFormat -> Either DirectionFormat ())
-> Prism' DirectionFormat ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (DirectionFormat -> () -> DirectionFormat
forall a b. a -> b -> a
const DirectionFormat
DirectionFormatShort) DirectionFormat -> Either DirectionFormat ()
f
where
f :: DirectionFormat -> Either DirectionFormat ()
f DirectionFormat
DirectionFormatShort = () -> Either DirectionFormat ()
forall a b. b -> Either a b
Right ()
f DirectionFormat
other = DirectionFormat -> Either DirectionFormat ()
forall a b. a -> Either a b
Left DirectionFormat
other
_DirectionFormatLong :: Prism' DirectionFormat ()
_DirectionFormatLong :: Prism' DirectionFormat ()
_DirectionFormatLong = (() -> DirectionFormat)
-> (DirectionFormat -> Either DirectionFormat ())
-> Prism' DirectionFormat ()
forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism (DirectionFormat -> () -> DirectionFormat
forall a b. a -> b -> a
const DirectionFormat
DirectionFormatLong) DirectionFormat -> Either DirectionFormat ()
f
where
f :: DirectionFormat -> Either DirectionFormat ()
f DirectionFormat
DirectionFormatLong = () -> Either DirectionFormat ()
forall a b. b -> Either a b
Right ()
f DirectionFormat
other = DirectionFormat -> Either DirectionFormat ()
forall a b. a -> Either a b
Left DirectionFormat
other
data DirectedFormatter = MkDirectedFormatter
{ DirectedFormatter -> CaseFormat
caseFormat :: CaseFormat,
DirectedFormatter -> DirectionFormat
directionFormat :: DirectionFormat
}
deriving stock
(
DirectedFormatter -> DirectedFormatter -> Bool
(DirectedFormatter -> DirectedFormatter -> Bool)
-> (DirectedFormatter -> DirectedFormatter -> Bool)
-> Eq DirectedFormatter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirectedFormatter -> DirectedFormatter -> Bool
== :: DirectedFormatter -> DirectedFormatter -> Bool
$c/= :: DirectedFormatter -> DirectedFormatter -> Bool
/= :: DirectedFormatter -> DirectedFormatter -> Bool
Eq,
Int -> DirectedFormatter -> ShowS
[DirectedFormatter] -> ShowS
DirectedFormatter -> String
(Int -> DirectedFormatter -> ShowS)
-> (DirectedFormatter -> String)
-> ([DirectedFormatter] -> ShowS)
-> Show DirectedFormatter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DirectedFormatter -> ShowS
showsPrec :: Int -> DirectedFormatter -> ShowS
$cshow :: DirectedFormatter -> String
show :: DirectedFormatter -> String
$cshowList :: [DirectedFormatter] -> ShowS
showList :: [DirectedFormatter] -> ShowS
Show
)
instance Default DirectedFormatter where
def :: DirectedFormatter
def = CaseFormat -> DirectionFormat -> DirectedFormatter
MkDirectedFormatter CaseFormat
CaseFormatLower DirectionFormat
forall a. Default a => a
def
instance
(k ~ A_Lens, a ~ CaseFormat, b ~ CaseFormat) =>
LabelOptic "caseFormat" k DirectedFormatter DirectedFormatter a b
where
labelOptic :: Optic k NoIx DirectedFormatter DirectedFormatter a b
labelOptic = (DirectedFormatter -> a)
-> (DirectedFormatter -> b -> DirectedFormatter)
-> Lens DirectedFormatter DirectedFormatter a b
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DirectedFormatter -> a
DirectedFormatter -> CaseFormat
caseFormat (\DirectedFormatter
f b
x -> DirectedFormatter
f {caseFormat = x})
instance
(k ~ A_Lens, a ~ DirectionFormat, b ~ DirectionFormat) =>
LabelOptic "directionFormat" k DirectedFormatter DirectedFormatter a b
where
labelOptic :: Optic k NoIx DirectedFormatter DirectedFormatter a b
labelOptic = (DirectedFormatter -> a)
-> (DirectedFormatter -> b -> DirectedFormatter)
-> Lens DirectedFormatter DirectedFormatter a b
forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens DirectedFormatter -> a
DirectedFormatter -> DirectionFormat
directionFormat (\DirectedFormatter
f b
x -> DirectedFormatter
f {directionFormat = x})
instance Formatter DirectedFormatter where
formatStr :: DirectedFormatter -> Text
formatStr DirectedFormatter
_ = Text
" %s"
directedFormatterUnix :: DirectedFormatter
directedFormatterUnix :: DirectedFormatter
directedFormatterUnix = CaseFormat -> DirectionFormat -> DirectedFormatter
MkDirectedFormatter CaseFormat
CaseFormatUpper DirectionFormat
DirectionFormatShort
directedFormatterVerbose :: DirectedFormatter
directedFormatterVerbose :: DirectedFormatter
directedFormatterVerbose = CaseFormat -> DirectionFormat -> DirectedFormatter
MkDirectedFormatter CaseFormat
CaseFormatLower DirectionFormat
DirectionFormatLong
formatDirection ::
( Directed a
) =>
DirectedFormatter ->
a ->
Text
formatDirection :: forall a. Directed a => DirectedFormatter -> a -> Text
formatDirection DirectedFormatter
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
$ DirectedFormatter -> Text
forall a. Formatter a => a -> Text
formatStr DirectedFormatter
fmt) Text
dir'
where
dir :: Text
dir = DirectionFormat -> Direction -> Text
formatDirection' (DirectedFormatter
fmt DirectedFormatter
-> Optic' A_Lens NoIx DirectedFormatter DirectionFormat
-> DirectionFormat
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx DirectedFormatter DirectionFormat
#directionFormat) (a -> Direction
forall a. Directed a => a -> Direction
directionOf a
x)
dir' :: Text
dir' = CaseFormat -> Text -> Text
caseFormatToFn (DirectedFormatter
fmt DirectedFormatter
-> Optic' A_Lens NoIx DirectedFormatter CaseFormat -> CaseFormat
forall k s (is :: IxList) a.
Is k A_Getter =>
s -> Optic' k is s a -> a
^. Optic' A_Lens NoIx DirectedFormatter CaseFormat
#caseFormat) Text
dir
formatDirection' :: DirectionFormat -> Direction -> Text
formatDirection' :: DirectionFormat -> Direction -> Text
formatDirection' DirectionFormat
DirectionFormatShort Direction
Up = Text
"U"
formatDirection' DirectionFormat
DirectionFormatShort Direction
Down = Text
"D"
formatDirection' DirectionFormat
DirectionFormatLong Direction
Up = Text
"Up"
formatDirection' DirectionFormat
DirectionFormatLong Direction
Down = Text
"Down"