{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
module JsonToHaskell
( jsonToHaskell
, simpleOptions
, performantOptions
, Options(..)
, NumberType(..)
, TextType(..)
, MapType(..)
, ListType(..)
) where
import JsonToHaskell.Internal.Options
import JsonToHaskell.Internal.Printer
import JsonToHaskell.Internal.Parser
import Data.Aeson (Value)
import qualified Data.Text as T
import qualified Data.Bimap as BM
jsonToHaskell :: Options -> Value -> T.Text
jsonToHaskell :: Options -> Value -> Text
jsonToHaskell Options
opts Value
v = do
let allStructs :: Map (RecordFields 'Structure) (NESet Text)
allStructs = Value -> Map (RecordFields 'Structure) (NESet Text)
analyze Value
v
namedStructs :: Bimap Text (RecordFields 'Structure)
namedStructs = Map (RecordFields 'Structure) (NESet Text)
-> Bimap Text (RecordFields 'Structure)
canonicalizeRecordNames Map (RecordFields 'Structure) (NESet Text)
allStructs
referencedStructs :: Bimap Text (HashMap Text (Struct 'Ref))
referencedStructs = (RecordFields 'Structure -> HashMap Text (Struct 'Ref))
-> Bimap Text (RecordFields 'Structure)
-> Bimap Text (HashMap Text (Struct 'Ref))
forall c b a. Ord c => (b -> c) -> Bimap a b -> Bimap a c
BM.mapR ((Struct 'Structure -> Struct 'Ref)
-> RecordFields 'Structure -> HashMap Text (Struct 'Ref)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Bimap Text (RecordFields 'Structure)
-> Struct 'Structure -> Struct 'Ref
addReferences Bimap Text (RecordFields 'Structure)
namedStructs)) Bimap Text (RecordFields 'Structure)
namedStructs
in Text -> Text
T.strip (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Options -> Bimap Text (HashMap Text (Struct 'Ref)) -> Text
writeModel Options
opts Bimap Text (HashMap Text (Struct 'Ref))
referencedStructs