module Data.Sv.Encode.Options (
EncodeOptions (EncodeOptions, _encodeSeparator, _spacingBefore, _spacingAfter, _quote, _newline, _terminalNewline)
, HasEncodeOptions (encodeOptions, spacingBefore, spacingAfter, quote, newline, terminalNewline)
, HasSeparator (..)
, defaultEncodeOptions
) where
import Control.Lens (Lens')
import Data.Sv.Syntax.Sv (Separator, HasSeparator (separator), comma)
import Text.Newline (Newline (CRLF))
import Text.Space (Spaces)
import Text.Quote (Quote (DoubleQuote))
data EncodeOptions =
EncodeOptions {
_encodeSeparator :: Separator
, _spacingBefore :: Spaces
, _spacingAfter :: Spaces
, _quote :: Maybe Quote
, _newline :: Newline
, _terminalNewline :: Bool
}
class HasSeparator c => HasEncodeOptions c where
encodeOptions :: Lens' c EncodeOptions
newline :: Lens' c Newline
quote :: Lens' c (Maybe Quote)
spacingAfter :: Lens' c Spaces
spacingBefore :: Lens' c Spaces
terminalNewline :: Lens' c Bool
newline = encodeOptions . newline
quote = encodeOptions . quote
spacingAfter = encodeOptions . spacingAfter
spacingBefore = encodeOptions . spacingBefore
terminalNewline = encodeOptions . terminalNewline
instance HasSeparator EncodeOptions where
separator f (EncodeOptions x1 x2 x3 x4 x5 x6) =
fmap (\ y -> EncodeOptions y x2 x3 x4 x5 x6) (f x1)
instance HasEncodeOptions EncodeOptions where
encodeOptions = id
newline f (EncodeOptions x1 x2 x3 x4 x5 x6) =
fmap (\ y -> EncodeOptions x1 x2 x3 x4 y x6) (f x5)
quote f (EncodeOptions x1 x2 x3 x4 x5 x6) =
fmap (\ y -> EncodeOptions x1 x2 x3 y x5 x6) (f x4)
spacingAfter f (EncodeOptions x1 x2 x3 x4 x5 x6) =
fmap (\ y -> EncodeOptions x1 x2 y x4 x5 x6) (f x3)
spacingBefore f (EncodeOptions x1 x2 x3 x4 x5 x6) =
fmap (\ y -> EncodeOptions x1 y x3 x4 x5 x6) (f x2)
terminalNewline f (EncodeOptions x1 x2 x3 x4 x5 x6) =
fmap (\ y -> EncodeOptions x1 x2 x3 x4 x5 y) (f x6)
defaultEncodeOptions :: EncodeOptions
defaultEncodeOptions = EncodeOptions comma mempty mempty (Just DoubleQuote) CRLF False