-- Needed to derive POSable
{-# LANGUAGE DeriveAnyClass  #-}
-- Needed to derive GHC.Generic
{-# LANGUAGE DeriveGeneric   #-}
-- To generate instances for ground types
{-# LANGUAGE TemplateHaskell #-}
-- Needed to determine the tag size at compile time
{-# OPTIONS_GHC -fplugin GHC.TypeLits.KnownNat.Solver #-}
-- Larger types need more iterations
{-# OPTIONS_GHC -fconstraint-solver-iterations=11 #-}

-- | Contains an example for deriving POSable for some datatype
module Examples () where

-- POSable re-exports SOP.Generic
import           GHC.Generics                    as GHC
import           Generics.POSable.POSable        as POSable
import           Generics.POSable.Representation
import           Generics.POSable.TH

data Test a b c = C1 a
                | C2 b
                | C3 c
                | C4 a a a a a a a
                | C5 a b c
    deriving ((forall x. Test a b c -> Rep (Test a b c) x)
-> (forall x. Rep (Test a b c) x -> Test a b c)
-> Generic (Test a b c)
forall x. Rep (Test a b c) x -> Test a b c
forall x. Test a b c -> Rep (Test a b c) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a b c x. Rep (Test a b c) x -> Test a b c
forall a b c x. Test a b c -> Rep (Test a b c) x
$cto :: forall a b c x. Rep (Test a b c) x -> Test a b c
$cfrom :: forall a b c x. Test a b c -> Rep (Test a b c) x
GHC.Generic, All SListI (Code (Test a b c))
All SListI (Code (Test a b c))
-> (Test a b c -> Rep (Test a b c))
-> (Rep (Test a b c) -> Test a b c)
-> Generic (Test a b c)
Rep (Test a b c) -> Test a b c
Test a b c -> Rep (Test a b c)
forall a.
All SListI (Code a) -> (a -> Rep a) -> (Rep a -> a) -> Generic a
forall a b c. All SListI (Code (Test a b c))
forall a b c. Rep (Test a b c) -> Test a b c
forall a b c. Test a b c -> Rep (Test a b c)
to :: Rep (Test a b c) -> Test a b c
$cto :: forall a b c. Rep (Test a b c) -> Test a b c
from :: Test a b c -> Rep (Test a b c)
$cfrom :: forall a b c. Test a b c -> Rep (Test a b c)
$cp1Generic :: forall a b c. All SListI (Code (Test a b c))
POSable.Generic, KnownNat (Choices (Test a b c))
[Integer]
ProductType (Fields (Test a b c))
KnownNat (Choices (Test a b c))
-> (Test a b c -> Finite (Choices (Test a b c)))
-> [Integer]
-> (Finite (Choices (Test a b c))
    -> Product (Fields (Test a b c)) -> Test a b c)
-> (Test a b c -> Product (Fields (Test a b c)))
-> ProductType (Fields (Test a b c))
-> POSable (Test a b c)
Finite (Choices (Test a b c))
-> Product (Fields (Test a b c)) -> Test a b c
Test a b c -> Finite (Choices (Test a b c))
Test a b c -> Product (Fields (Test a b c))
forall x.
KnownNat (Choices x)
-> (x -> Finite (Choices x))
-> [Integer]
-> (Finite (Choices x) -> Product (Fields x) -> x)
-> (x -> Product (Fields x))
-> ProductType (Fields x)
-> POSable x
forall a b c.
(POSable a, POSable b, POSable c) =>
KnownNat (Choices (Test a b c))
forall a b c. (POSable a, POSable b, POSable c) => [Integer]
forall a b c.
(POSable a, POSable b, POSable c) =>
ProductType (Fields (Test a b c))
forall a b c.
(POSable a, POSable b, POSable c) =>
Finite (Choices (Test a b c))
-> Product (Fields (Test a b c)) -> Test a b c
forall a b c.
(POSable a, POSable b, POSable c) =>
Test a b c -> Finite (Choices (Test a b c))
forall a b c.
(POSable a, POSable b, POSable c) =>
Test a b c -> Product (Fields (Test a b c))
emptyFields :: ProductType (Fields (Test a b c))
$cemptyFields :: forall a b c.
(POSable a, POSable b, POSable c) =>
ProductType (Fields (Test a b c))
fields :: Test a b c -> Product (Fields (Test a b c))
$cfields :: forall a b c.
(POSable a, POSable b, POSable c) =>
Test a b c -> Product (Fields (Test a b c))
fromPOSable :: Finite (Choices (Test a b c))
-> Product (Fields (Test a b c)) -> Test a b c
$cfromPOSable :: forall a b c.
(POSable a, POSable b, POSable c) =>
Finite (Choices (Test a b c))
-> Product (Fields (Test a b c)) -> Test a b c
tags :: [Integer]
$ctags :: forall a b c. (POSable a, POSable b, POSable c) => [Integer]
choices :: Test a b c -> Finite (Choices (Test a b c))
$cchoices :: forall a b c.
(POSable a, POSable b, POSable c) =>
Test a b c -> Finite (Choices (Test a b c))
$cp1POSable :: forall a b c.
(POSable a, POSable b, POSable c) =>
KnownNat (Choices (Test a b c))
POSable)

-- Define a set of types that can be the ground types of the POSable
-- representation. Only types in this set can occur in Fields.
instance Ground Float where
  mkGround :: Float
mkGround = Float
0.0

instance Ground Double where
  mkGround :: Double
mkGround = Double
0


-- Define a POSable instance for these ground types
mkPOSableGround ''Float

mkPOSableGround ''Double