{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE GADTSyntax #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-} -- the reason for this being in its own module
{-# OPTIONS_GHC -Wno-orphans #-}
module Codec.Candid.Generic (AsRecord(..), AsVariant(..)) where

import qualified Data.Row as R
import qualified Data.Row.Records as R
import qualified Data.Row.Variants as V
import Data.Typeable

import Codec.Candid.Class

-- | This newtype encodes a Haskell record type using generic programming. Best used with @DerivingVia@, as shown in the tutorial.
newtype AsRecord a = AsRecord { forall a. AsRecord a -> a
unAsRecord :: a }


type CanBeCandidRecord a =
    ( Typeable a
    , Candid (R.Rec (R.NativeRow a))
    , R.ToNative a
    , R.FromNative a
    )
instance CanBeCandidRecord a => Candid (AsRecord a) where
    type AsCandid (AsRecord a) = AsCandid (R.Rec (R.NativeRow a))
    toCandid :: AsRecord a -> AsCandid (AsRecord a)
toCandid = forall a. Candid a => a -> AsCandid a
toCandid @(R.Rec (R.NativeRow a)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. FromNative t => t -> Rec (NativeRow t)
R.fromNative forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. AsRecord a -> a
unAsRecord
    fromCandid :: AsCandid (AsRecord a) -> AsRecord a
fromCandid = forall a. a -> AsRecord a
AsRecord forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. ToNative t => Rec (NativeRow t) -> t
R.toNative forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Candid a => AsCandid a -> a
fromCandid @(R.Rec (R.NativeRow a))

-- | This newtype encodes a Haskell data type as a variant using generic programming. Best used with @DerivingVia@, as shown in the tutorial.
newtype AsVariant a = AsVariant { forall a. AsVariant a -> a
unAsVariant :: a }

type CanBeCandidVariant a =
    ( Typeable a
    , Candid (V.Var (V.NativeRow a))
    , V.ToNative a
    , V.FromNative a
    )

instance CanBeCandidVariant a => Candid (AsVariant a) where
    type AsCandid (AsVariant a) = AsCandid (V.Var (V.NativeRow a))
    toCandid :: AsVariant a -> AsCandid (AsVariant a)
toCandid = forall a. Candid a => a -> AsCandid a
toCandid @(V.Var (V.NativeRow a)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. FromNative t => t -> Var (NativeRow t)
V.fromNative forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. AsVariant a -> a
unAsVariant
    fromCandid :: AsCandid (AsVariant a) -> AsVariant a
fromCandid = forall a. a -> AsVariant a
AsVariant forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. ToNative t => Var (NativeRow t) -> t
V.toNative forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Candid a => AsCandid a -> a
fromCandid @(V.Var (V.NativeRow a))