{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
module Stype.Aeson (
) where
import Data.Aeson
import Stype.Numeric ( Count
, Continuous(..)
, NonnegContinuous(..)
, EventTime(..)
, MaybeCensored )
import Stype.Categorical ( Nominal
, Binary
, toBool )
import Data.Text
instance ToJSON Count where
instance ToJSON a => ToJSON (Continuous a) where
toJSON :: Continuous a -> Value
toJSON (Cont a
x) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
x
toJSON Continuous a
NegContInf = Value
"-Inf"
toJSON Continuous a
ContInf = Value
"Inf"
instance ToJSON a => ToJSON (NonnegContinuous a) where
toJSON :: NonnegContinuous a -> Value
toJSON (NonNegCont a
x) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
x
toJSON NonnegContinuous a
NonNegContInf = Value
"Inf"
instance ToJSON a => ToJSON (EventTime a) where
toJSON :: EventTime a -> Value
toJSON (EventTime NonnegContinuous a
x) = NonnegContinuous a -> Value
forall a. ToJSON a => a -> Value
toJSON NonnegContinuous a
x
instance ToJSON a => ToJSON (MaybeCensored a) where
instance ToJSON a => ToJSON (Nominal a) where
instance ToJSON Binary where
toJSON :: Binary -> Value
toJSON Binary
x = Bool -> Value
forall a. ToJSON a => a -> Value
toJSON (Binary -> Bool
toBool Binary
x)