{-# language DataKinds             #-}
{-# language DeriveAnyClass        #-}
{-# language DeriveGeneric         #-}
{-# language DerivingVia           #-}
{-# language FlexibleInstances     #-}
{-# language GADTs                 #-}
{-# language MultiParamTypeClasses #-}
{-# language PolyKinds             #-}
{-# language QuasiQuotes           #-}
{-# language StandaloneDeriving    #-}
{-# language TemplateHaskell       #-}
{-# language TypeApplications      #-}
{-# language TypeFamilies          #-}
{-# language TypeOperators         #-}
{-# language UndecidableInstances  #-}
{-|
Description : Examples for schema definitions.

Look at the source code of this module.
-}
module Mu.Schema.Examples where

import qualified Data.Aeson                         as J
import           Data.Functor.Identity
import qualified Data.Text                          as T
import           GHC.Generics

import           Mu.Adapter.Json                    ()
import           Mu.Schema
import           Mu.Schema.Conversion.SchemaToTypes

data Person
  = Person { Person -> Text
firstName :: T.Text
           , Person -> Text
lastName  :: T.Text
           , Person -> Maybe Int
age       :: Maybe Int
           , Person -> Maybe Gender
gender    :: Maybe Gender
           , Person -> Address
address   :: Address }
  deriving (Person -> Person -> Bool
(Person -> Person -> Bool)
-> (Person -> Person -> Bool) -> Eq Person
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Person -> Person -> Bool
$c/= :: Person -> Person -> Bool
== :: Person -> Person -> Bool
$c== :: Person -> Person -> Bool
Eq, Int -> Person -> ShowS
[Person] -> ShowS
Person -> String
(Int -> Person -> ShowS)
-> (Person -> String) -> ([Person] -> ShowS) -> Show Person
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Person] -> ShowS
$cshowList :: [Person] -> ShowS
show :: Person -> String
$cshow :: Person -> String
showsPrec :: Int -> Person -> ShowS
$cshowsPrec :: Int -> Person -> ShowS
Show, (forall x. Person -> Rep Person x)
-> (forall x. Rep Person x -> Person) -> Generic Person
forall x. Rep Person x -> Person
forall x. Person -> Rep Person x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Person x -> Person
$cfrom :: forall x. Person -> Rep Person x
Generic)
  deriving (ToSchema Identity ExampleSchema "person", FromSchema Identity ExampleSchema "person")
  deriving ([Person] -> Encoding
[Person] -> Value
Person -> Encoding
Person -> Value
(Person -> Value)
-> (Person -> Encoding)
-> ([Person] -> Value)
-> ([Person] -> Encoding)
-> ToJSON Person
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Person] -> Encoding
$ctoEncodingList :: [Person] -> Encoding
toJSONList :: [Person] -> Value
$ctoJSONList :: [Person] -> Value
toEncoding :: Person -> Encoding
$ctoEncoding :: Person -> Encoding
toJSON :: Person -> Value
$ctoJSON :: Person -> Value
J.ToJSON, Value -> Parser [Person]
Value -> Parser Person
(Value -> Parser Person)
-> (Value -> Parser [Person]) -> FromJSON Person
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Person]
$cparseJSONList :: Value -> Parser [Person]
parseJSON :: Value -> Parser Person
$cparseJSON :: Value -> Parser Person
J.FromJSON)
    via (WithSchema Identity ExampleSchema "person" Person)

data Address
  = Address { Address -> Text
postcode :: T.Text
            , Address -> Text
country  :: T.Text }
  deriving (Address -> Address -> Bool
(Address -> Address -> Bool)
-> (Address -> Address -> Bool) -> Eq Address
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Address -> Address -> Bool
$c/= :: Address -> Address -> Bool
== :: Address -> Address -> Bool
$c== :: Address -> Address -> Bool
Eq, Int -> Address -> ShowS
[Address] -> ShowS
Address -> String
(Int -> Address -> ShowS)
-> (Address -> String) -> ([Address] -> ShowS) -> Show Address
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Address] -> ShowS
$cshowList :: [Address] -> ShowS
show :: Address -> String
$cshow :: Address -> String
showsPrec :: Int -> Address -> ShowS
$cshowsPrec :: Int -> Address -> ShowS
Show, (forall x. Address -> Rep Address x)
-> (forall x. Rep Address x -> Address) -> Generic Address
forall x. Rep Address x -> Address
forall x. Address -> Rep Address x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Address x -> Address
$cfrom :: forall x. Address -> Rep Address x
Generic)
  deriving (ToSchema Identity ExampleSchema "address", FromSchema Identity ExampleSchema "address")
  deriving ([Address] -> Encoding
[Address] -> Value
Address -> Encoding
Address -> Value
(Address -> Value)
-> (Address -> Encoding)
-> ([Address] -> Value)
-> ([Address] -> Encoding)
-> ToJSON Address
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Address] -> Encoding
$ctoEncodingList :: [Address] -> Encoding
toJSONList :: [Address] -> Value
$ctoJSONList :: [Address] -> Value
toEncoding :: Address -> Encoding
$ctoEncoding :: Address -> Encoding
toJSON :: Address -> Value
$ctoJSON :: Address -> Value
J.ToJSON, Value -> Parser [Address]
Value -> Parser Address
(Value -> Parser Address)
-> (Value -> Parser [Address]) -> FromJSON Address
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Address]
$cparseJSONList :: Value -> Parser [Address]
parseJSON :: Value -> Parser Address
$cparseJSON :: Value -> Parser Address
J.FromJSON)
    via (WithSchema Identity ExampleSchema "address" Address)

type GenderFieldMapping
  = '[ "Male"      ':-> "male"
     , "Female"    ':-> "female"
     , "NonBinary" ':-> "nb" ]

data Gender = Male | Female | NonBinary
  deriving (Gender -> Gender -> Bool
(Gender -> Gender -> Bool)
-> (Gender -> Gender -> Bool) -> Eq Gender
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Gender -> Gender -> Bool
$c/= :: Gender -> Gender -> Bool
== :: Gender -> Gender -> Bool
$c== :: Gender -> Gender -> Bool
Eq, Int -> Gender -> ShowS
[Gender] -> ShowS
Gender -> String
(Int -> Gender -> ShowS)
-> (Gender -> String) -> ([Gender] -> ShowS) -> Show Gender
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Gender] -> ShowS
$cshowList :: [Gender] -> ShowS
show :: Gender -> String
$cshow :: Gender -> String
showsPrec :: Int -> Gender -> ShowS
$cshowsPrec :: Int -> Gender -> ShowS
Show, (forall x. Gender -> Rep Gender x)
-> (forall x. Rep Gender x -> Gender) -> Generic Gender
forall x. Rep Gender x -> Gender
forall x. Gender -> Rep Gender x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Gender x -> Gender
$cfrom :: forall x. Gender -> Rep Gender x
Generic)
  deriving (ToSchema f ExampleSchema "gender", FromSchema f ExampleSchema "gender")
    via (CustomFieldMapping "gender" GenderFieldMapping Gender)
  deriving ([Gender] -> Encoding
[Gender] -> Value
Gender -> Encoding
Gender -> Value
(Gender -> Value)
-> (Gender -> Encoding)
-> ([Gender] -> Value)
-> ([Gender] -> Encoding)
-> ToJSON Gender
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Gender] -> Encoding
$ctoEncodingList :: [Gender] -> Encoding
toJSONList :: [Gender] -> Value
$ctoJSONList :: [Gender] -> Value
toEncoding :: Gender -> Encoding
$ctoEncoding :: Gender -> Encoding
toJSON :: Gender -> Value
$ctoJSON :: Gender -> Value
J.ToJSON, Value -> Parser [Gender]
Value -> Parser Gender
(Value -> Parser Gender)
-> (Value -> Parser [Gender]) -> FromJSON Gender
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Gender]
$cparseJSONList :: Value -> Parser [Gender]
parseJSON :: Value -> Parser Gender
$cparseJSON :: Value -> Parser Gender
J.FromJSON)
    via (WithSchema Identity ExampleSchema "gender" Gender)

-- Schema for these data types
type ExampleSchema
  = '[ 'DEnum   "gender"
               '[ 'ChoiceDef "male"
                , 'ChoiceDef "female"
                , 'ChoiceDef "nb" ]
     , 'DRecord "address"
               '[ 'FieldDef "postcode" ('TPrimitive T.Text)
                , 'FieldDef "country"  ('TPrimitive T.Text) ]
     , 'DRecord "person"
                '[ 'FieldDef "firstName" ('TPrimitive T.Text)
                 , 'FieldDef "lastName"  ('TPrimitive T.Text)
                 , 'FieldDef "age"       ('TOption ('TPrimitive Int))
                 , 'FieldDef "gender"    ('TOption ('TSchematic "gender"))
                 , 'FieldDef "address"   ('TSchematic "address") ]
     ]

$(generateTypesFromSchema (++"Msg") ''ExampleSchema)

{-
type ExampleSchema2
  = SchemaFromTypes '[ AsRecord Person "person"
                     , AsRecord Address "address"
                     , AsEnum Gender "gender" ]
-}
type ExampleSchema2
  = '[ 'DEnum   "gender"
               '[ 'ChoiceDef "Male"
                , 'ChoiceDef "Female"
                , 'ChoiceDef "NonBinary" ]
     , 'DRecord "address"
               '[ 'FieldDef "postcode" ('TPrimitive T.Text)
                , 'FieldDef "country"  ('TPrimitive T.Text) ]
     , 'DRecord "person"
                '[ 'FieldDef "firstName" ('TPrimitive T.Text)
                 , 'FieldDef "lastName"  ('TPrimitive T.Text)
                 , 'FieldDef "age"       ('TOption ('TPrimitive Int))
                 , 'FieldDef "gender"    ('TOption ('TSchematic "gender"))
                 , 'FieldDef "address"   ('TSchematic "address") ]
     ]

type ExampleRegistry
  = '[ 2 ':-> ExampleSchema2, 1 ':-> ExampleSchema]