{-# LANGUAGE RecordWildCards #-}
module Potato.Flow.Configuration where
import Relude
import Potato.Data.Text.Unicode
import Data.Default
import Data.Int
import qualified Text.Show
data PotatoConfiguration = PotatoConfiguration {
PotatoConfiguration -> Bool
_potatoConfiguration_allowGraphemeClusters :: Bool
, PotatoConfiguration -> Maybe (Maybe Char)
_potatoConfiguration_allowOrReplaceUnicodeWideChars :: Maybe (Maybe Char)
, PotatoConfiguration -> Char -> Int8
_potatoConfiguration_unicodeWideCharFn :: Char -> Int8
}
instance Show PotatoConfiguration where
show :: PotatoConfiguration -> String
show PotatoConfiguration {Bool
Maybe (Maybe Char)
Char -> Int8
_potatoConfiguration_unicodeWideCharFn :: Char -> Int8
_potatoConfiguration_allowOrReplaceUnicodeWideChars :: Maybe (Maybe Char)
_potatoConfiguration_allowGraphemeClusters :: Bool
_potatoConfiguration_unicodeWideCharFn :: PotatoConfiguration -> Char -> Int8
_potatoConfiguration_allowOrReplaceUnicodeWideChars :: PotatoConfiguration -> Maybe (Maybe Char)
_potatoConfiguration_allowGraphemeClusters :: PotatoConfiguration -> Bool
..} = String
"_potatoConfiguration_allowGraphemeClusters: " forall a. Semigroup a => a -> a -> a
<> forall b a. (Show a, IsString b) => a -> b
show Bool
_potatoConfiguration_allowGraphemeClusters forall a. Semigroup a => a -> a -> a
<> String
"\n_potatoConfiguration_allowOrReplaceUnicodeWideChars: " forall a. Semigroup a => a -> a -> a
<> forall b a. (Show a, IsString b) => a -> b
show Maybe (Maybe Char)
_potatoConfiguration_allowOrReplaceUnicodeWideChars
instance Default PotatoConfiguration where
def :: PotatoConfiguration
def = PotatoConfiguration {
_potatoConfiguration_allowGraphemeClusters :: Bool
_potatoConfiguration_allowGraphemeClusters = Bool
False
, _potatoConfiguration_allowOrReplaceUnicodeWideChars :: Maybe (Maybe Char)
_potatoConfiguration_allowOrReplaceUnicodeWideChars = forall a. a -> Maybe a
Just (forall a. a -> Maybe a
Just Char
'☺')
, _potatoConfiguration_unicodeWideCharFn :: Char -> Int8
_potatoConfiguration_unicodeWideCharFn = Char -> Int8
getCharWidth
}