{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
module Nix.Atoms where
#if MIN_VERSION_serialise(0, 2, 0)
import Codec.Serialise
#endif
import Control.DeepSeq
import Data.Data
import Data.Hashable
import Data.Text (Text, pack)
import GHC.Generics
data NAtom
= NInt Integer
| NFloat Float
| NBool Bool
| NNull
deriving (Eq, Ord, Generic, Typeable, Data, Show, Read, NFData,
Hashable)
#if MIN_VERSION_serialise(0, 2, 0)
instance Serialise NAtom
#endif
atomText :: NAtom -> Text
atomText (NInt i) = pack (show i)
atomText (NFloat f) = pack (show f)
atomText (NBool b) = if b then "true" else "false"
atomText NNull = "null"