{-|
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
-}

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-}

module EventData.Context.Domain.Demographics(
      DemographicsFacts(..)
    , DemographicsInfo(..)
    , DemographicsField(..)
    , demo
    , field 
    , info
) where

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

newtype DemographicsFacts = 
    DemographicsFacts { DemographicsFacts -> DemographicsInfo
_demo :: DemographicsInfo
                      } deriving( DemographicsFacts -> DemographicsFacts -> Bool
(DemographicsFacts -> DemographicsFacts -> Bool)
-> (DemographicsFacts -> DemographicsFacts -> Bool)
-> Eq DemographicsFacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DemographicsFacts -> DemographicsFacts -> Bool
$c/= :: DemographicsFacts -> DemographicsFacts -> Bool
== :: DemographicsFacts -> DemographicsFacts -> Bool
$c== :: DemographicsFacts -> DemographicsFacts -> Bool
Eq, Int -> DemographicsFacts -> ShowS
[DemographicsFacts] -> ShowS
DemographicsFacts -> String
(Int -> DemographicsFacts -> ShowS)
-> (DemographicsFacts -> String)
-> ([DemographicsFacts] -> ShowS)
-> Show DemographicsFacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DemographicsFacts] -> ShowS
$cshowList :: [DemographicsFacts] -> ShowS
show :: DemographicsFacts -> String
$cshow :: DemographicsFacts -> String
showsPrec :: Int -> DemographicsFacts -> ShowS
$cshowsPrec :: Int -> DemographicsFacts -> ShowS
Show, (forall x. DemographicsFacts -> Rep DemographicsFacts x)
-> (forall x. Rep DemographicsFacts x -> DemographicsFacts)
-> Generic DemographicsFacts
forall x. Rep DemographicsFacts x -> DemographicsFacts
forall x. DemographicsFacts -> Rep DemographicsFacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DemographicsFacts x -> DemographicsFacts
$cfrom :: forall x. DemographicsFacts -> Rep DemographicsFacts x
Generic )

data DemographicsInfo = 
    DemographicsInfo { DemographicsInfo -> DemographicsField
_field :: DemographicsField
                     , DemographicsInfo -> Maybe Text
_info :: Maybe Text
                     } deriving ( DemographicsInfo -> DemographicsInfo -> Bool
(DemographicsInfo -> DemographicsInfo -> Bool)
-> (DemographicsInfo -> DemographicsInfo -> Bool)
-> Eq DemographicsInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DemographicsInfo -> DemographicsInfo -> Bool
$c/= :: DemographicsInfo -> DemographicsInfo -> Bool
== :: DemographicsInfo -> DemographicsInfo -> Bool
$c== :: DemographicsInfo -> DemographicsInfo -> Bool
Eq, Int -> DemographicsInfo -> ShowS
[DemographicsInfo] -> ShowS
DemographicsInfo -> String
(Int -> DemographicsInfo -> ShowS)
-> (DemographicsInfo -> String)
-> ([DemographicsInfo] -> ShowS)
-> Show DemographicsInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DemographicsInfo] -> ShowS
$cshowList :: [DemographicsInfo] -> ShowS
show :: DemographicsInfo -> String
$cshow :: DemographicsInfo -> String
showsPrec :: Int -> DemographicsInfo -> ShowS
$cshowsPrec :: Int -> DemographicsInfo -> ShowS
Show, (forall x. DemographicsInfo -> Rep DemographicsInfo x)
-> (forall x. Rep DemographicsInfo x -> DemographicsInfo)
-> Generic DemographicsInfo
forall x. Rep DemographicsInfo x -> DemographicsInfo
forall x. DemographicsInfo -> Rep DemographicsInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DemographicsInfo x -> DemographicsInfo
$cfrom :: forall x. DemographicsInfo -> Rep DemographicsInfo x
Generic )

data DemographicsField =
      BirthYear
    | BirthDate
    | Race
    | RaceCodes
    | Gender
    | Zipcode
    | County
    | CountyFIPS
    | State
    | Ethnicity
    | Region
    | UrbanRural
    | GeoPctAmIndian
    | GeoPctAsian
    | GeoPctBlack
    | GeoPctHispanic
    | GeoPctMutli
    | GeoPctOther
    | GeoPctWhite
    | GeoType
    | GeoAdiStateRank
    | GeoAdiNatRank
    deriving ( DemographicsField -> DemographicsField -> Bool
(DemographicsField -> DemographicsField -> Bool)
-> (DemographicsField -> DemographicsField -> Bool)
-> Eq DemographicsField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DemographicsField -> DemographicsField -> Bool
$c/= :: DemographicsField -> DemographicsField -> Bool
== :: DemographicsField -> DemographicsField -> Bool
$c== :: DemographicsField -> DemographicsField -> Bool
Eq, Int -> DemographicsField -> ShowS
[DemographicsField] -> ShowS
DemographicsField -> String
(Int -> DemographicsField -> ShowS)
-> (DemographicsField -> String)
-> ([DemographicsField] -> ShowS)
-> Show DemographicsField
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DemographicsField] -> ShowS
$cshowList :: [DemographicsField] -> ShowS
show :: DemographicsField -> String
$cshow :: DemographicsField -> String
showsPrec :: Int -> DemographicsField -> ShowS
$cshowsPrec :: Int -> DemographicsField -> ShowS
Show, (forall x. DemographicsField -> Rep DemographicsField x)
-> (forall x. Rep DemographicsField x -> DemographicsField)
-> Generic DemographicsField
forall x. Rep DemographicsField x -> DemographicsField
forall x. DemographicsField -> Rep DemographicsField x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DemographicsField x -> DemographicsField
$cfrom :: forall x. DemographicsField -> Rep DemographicsField x
Generic )

makeLenses ''DemographicsFacts
makeLenses ''DemographicsInfo

instance FromJSON DemographicsFacts where
  parseJSON :: Value -> Parser DemographicsFacts
parseJSON = Options -> Value -> Parser DemographicsFacts
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}
instance FromJSON DemographicsInfo where
  parseJSON :: Value -> Parser DemographicsInfo
parseJSON = Options -> Value -> Parser DemographicsInfo
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}
instance FromJSON DemographicsField where