{-|
Module      : Event Data Model facts 
Description : Defines the Context type and its component types, constructors, 
              and class instances
Copyright   : (c) NoviSci, Inc 2020
License     : BSD3
Maintainer  : bsaul@novisci.com
-}
{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}

module EventData.Context.Domain.Enrollment(
  EnrollmentFacts(..)
) where

import Control.Lens             ( makeLenses )
import Data.Aeson               ( FromJSON(..)
                                , genericParseJSON
                                , defaultOptions
                                , fieldLabelModifier )
import Data.List                ( drop )
import Data.Eq                  ( Eq )
import GHC.Generics             ( Generic )
import GHC.Show                 ( Show )

-- data Plan = Plan 

-- | An enrollment fact
newtype EnrollmentFacts = EnrollmentFacts {
     EnrollmentFacts -> ()
_plan :: () -- TODO add plan fact
  } 
  deriving( EnrollmentFacts -> EnrollmentFacts -> Bool
(EnrollmentFacts -> EnrollmentFacts -> Bool)
-> (EnrollmentFacts -> EnrollmentFacts -> Bool)
-> Eq EnrollmentFacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnrollmentFacts -> EnrollmentFacts -> Bool
$c/= :: EnrollmentFacts -> EnrollmentFacts -> Bool
== :: EnrollmentFacts -> EnrollmentFacts -> Bool
$c== :: EnrollmentFacts -> EnrollmentFacts -> Bool
Eq, Int -> EnrollmentFacts -> ShowS
[EnrollmentFacts] -> ShowS
EnrollmentFacts -> String
(Int -> EnrollmentFacts -> ShowS)
-> (EnrollmentFacts -> String)
-> ([EnrollmentFacts] -> ShowS)
-> Show EnrollmentFacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnrollmentFacts] -> ShowS
$cshowList :: [EnrollmentFacts] -> ShowS
show :: EnrollmentFacts -> String
$cshow :: EnrollmentFacts -> String
showsPrec :: Int -> EnrollmentFacts -> ShowS
$cshowsPrec :: Int -> EnrollmentFacts -> ShowS
Show, (forall x. EnrollmentFacts -> Rep EnrollmentFacts x)
-> (forall x. Rep EnrollmentFacts x -> EnrollmentFacts)
-> Generic EnrollmentFacts
forall x. Rep EnrollmentFacts x -> EnrollmentFacts
forall x. EnrollmentFacts -> Rep EnrollmentFacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnrollmentFacts x -> EnrollmentFacts
$cfrom :: forall x. EnrollmentFacts -> Rep EnrollmentFacts x
Generic )

makeLenses ''EnrollmentFacts

instance FromJSON EnrollmentFacts where
  parseJSON :: Value -> Parser EnrollmentFacts
parseJSON = Options -> Value -> Parser EnrollmentFacts
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
defaultOptions{fieldLabelModifier :: ShowS
fieldLabelModifier = Int -> ShowS
forall a. Int -> [a] -> [a]
drop Int
1}