{-# LANGUAGE TemplateHaskell #-}
module JsonToHaskell.Internal.Options where

import Lens.Micro.Platform (makeLenses)

-- | Choose which type to use for Numbers
data NumberType =
    -- | Use 'Int' for whole numbers, 'Float' for decimals
    UseSmartFloats
    -- | Use 'Int' for whole numbers, 'Double' for decimals
  | UseSmartDoubles
    -- | Use 'Float' for all numbers
  | UseFloats
    -- | Use 'Double' for all numbers
  | UseDoubles
    -- | Use 'Scientific' for all numbers
  | UseScientificNumbers
  deriving (Int -> NumberType -> ShowS
[NumberType] -> ShowS
NumberType -> String
(Int -> NumberType -> ShowS)
-> (NumberType -> String)
-> ([NumberType] -> ShowS)
-> Show NumberType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NumberType] -> ShowS
$cshowList :: [NumberType] -> ShowS
show :: NumberType -> String
$cshow :: NumberType -> String
showsPrec :: Int -> NumberType -> ShowS
$cshowsPrec :: Int -> NumberType -> ShowS
Show, NumberType -> NumberType -> Bool
(NumberType -> NumberType -> Bool)
-> (NumberType -> NumberType -> Bool) -> Eq NumberType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NumberType -> NumberType -> Bool
$c/= :: NumberType -> NumberType -> Bool
== :: NumberType -> NumberType -> Bool
$c== :: NumberType -> NumberType -> Bool
Eq)

-- | Choose which type to use for strings
data TextType =
    -- | Use 'String' for strings
    UseString
    -- | Use 'Text' for string
  | UseText
    -- | Use 'ByteString' for strings
  | UseByteString
  deriving (Int -> TextType -> ShowS
[TextType] -> ShowS
TextType -> String
(Int -> TextType -> ShowS)
-> (TextType -> String) -> ([TextType] -> ShowS) -> Show TextType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextType] -> ShowS
$cshowList :: [TextType] -> ShowS
show :: TextType -> String
$cshow :: TextType -> String
showsPrec :: Int -> TextType -> ShowS
$cshowsPrec :: Int -> TextType -> ShowS
Show, TextType -> TextType -> Bool
(TextType -> TextType -> Bool)
-> (TextType -> TextType -> Bool) -> Eq TextType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextType -> TextType -> Bool
$c/= :: TextType -> TextType -> Bool
== :: TextType -> TextType -> Bool
$c== :: TextType -> TextType -> Bool
Eq)

-- | Choose which type to use for key-value maps
data MapType =
    -- | Use Data.Map
    UseMap
    -- | Use Data.HashMap
  | UseHashMap
  deriving (Int -> MapType -> ShowS
[MapType] -> ShowS
MapType -> String
(Int -> MapType -> ShowS)
-> (MapType -> String) -> ([MapType] -> ShowS) -> Show MapType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MapType] -> ShowS
$cshowList :: [MapType] -> ShowS
show :: MapType -> String
$cshow :: MapType -> String
showsPrec :: Int -> MapType -> ShowS
$cshowsPrec :: Int -> MapType -> ShowS
Show, MapType -> MapType -> Bool
(MapType -> MapType -> Bool)
-> (MapType -> MapType -> Bool) -> Eq MapType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MapType -> MapType -> Bool
$c/= :: MapType -> MapType -> Bool
== :: MapType -> MapType -> Bool
$c== :: MapType -> MapType -> Bool
Eq)

-- | Choose which type to use for arrays
data ListType =
    -- | Use lists
    UseList
    -- | Use vectors
  | UseVector
  deriving (Int -> ListType -> ShowS
[ListType] -> ShowS
ListType -> String
(Int -> ListType -> ShowS)
-> (ListType -> String) -> ([ListType] -> ShowS) -> Show ListType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListType] -> ShowS
$cshowList :: [ListType] -> ShowS
show :: ListType -> String
$cshow :: ListType -> String
showsPrec :: Int -> ListType -> ShowS
$cshowsPrec :: Int -> ListType -> ShowS
Show, ListType -> ListType -> Bool
(ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool) -> Eq ListType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListType -> ListType -> Bool
$c/= :: ListType -> ListType -> Bool
== :: ListType -> ListType -> Bool
$c== :: ListType -> ListType -> Bool
Eq)

-- | Options for module generation
data Options = Options
  { Options -> Int
_tabStop :: Int
  , Options -> NumberType
_numberType :: NumberType
  , Options -> TextType
_textType :: TextType
  , Options -> MapType
_mapType :: MapType
  , Options -> ListType
_listType :: ListType
  , Options -> Bool
_includeHeader :: Bool
  -- , _stronglyNormalize :: Bool
  , Options -> Bool
_strictData :: Bool
  }


makeLenses ''Options

-- | Simple module generation options.
-- These are reasonable defaults for a simple module
simpleOptions :: Options
simpleOptions :: Options
simpleOptions = Options :: Int
-> NumberType
-> TextType
-> MapType
-> ListType
-> Bool
-> Bool
-> Options
Options
    { _tabStop :: Int
_tabStop = Int
2
    , _numberType :: NumberType
_numberType = NumberType
UseDoubles
    , _textType :: TextType
_textType = TextType
UseText
    , _mapType :: MapType
_mapType = MapType
UseMap
    , _listType :: ListType
_listType = ListType
UseList
    , _includeHeader :: Bool
_includeHeader = Bool
False
    -- , _stronglyNormalize = True
    , _strictData :: Bool
_strictData = Bool
False
    }

-- | Use more performant data types, use these for production apps.
performantOptions :: Options
performantOptions :: Options
performantOptions = Options :: Int
-> NumberType
-> TextType
-> MapType
-> ListType
-> Bool
-> Bool
-> Options
Options
    { _tabStop :: Int
_tabStop = Int
2
    , _numberType :: NumberType
_numberType = NumberType
UseDoubles
    , _textType :: TextType
_textType = TextType
UseText
    , _mapType :: MapType
_mapType = MapType
UseMap
    , _listType :: ListType
_listType = ListType
UseList
    , _includeHeader :: Bool
_includeHeader = Bool
False
    -- TODO
    -- , _stronglyNormalize = True
    , _strictData :: Bool
_strictData = Bool
True
    }