{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  ToySolver.Version
-- Copyright   :  (c) Masahiro Sakai 2013
-- License     :  BSD-style
--
-- Maintainer  :  masahiro.sakai@gmail.com
-- Stability   :  provisional
-- Portability :  non-portable
--
-----------------------------------------------------------------------------
module ToySolver.Version
  ( version
  , packageVersions
  , gitHash
  , compilationTime
  ) where

import Data.List
import Data.Time
import Data.Version
import ToySolver.Version.TH
import Paths_toysolver

packageVersions :: [(String, String)]
packageVersions :: [(String, String)]
packageVersions = forall a. Ord a => [a] -> [a]
sort forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
tail
  [ (forall a. HasCallStack => a
undefined, forall a. HasCallStack => a
undefined) -- dummy
#ifdef VERSION_MIP
  , (String
"MIP", VERSION_MIP)
#endif
#ifdef VERSION_OpenCL
  , ("OpenCL", VERSION_OpenCL)
#endif
#ifdef VERSION_OptDir
  , (String
"OptDir", VERSION_OptDir)
#endif
#ifdef VERSION_ansi_wl_pprint
  , ("ansi-wl-pprint", VERSION_ansi_wl_pprint)
#endif
#ifdef VERSION_array
  , (String
"array", VERSION_array)
#endif
#ifdef VERSION_attoparsec
  , ("attoparsec", VERSION_attoparsec)
#endif
#ifdef VERSION_base
  , (String
"base", VERSION_base)
#endif
#ifdef VERSION_bytestring
  , (String
"bytestring", VERSION_bytestring)
#endif
#ifdef VERSION_bytestring_builder
  , (String
"bytestring-builder", VERSION_bytestring_builder)
#endif
#ifdef VERSION_bytestring_encoding
  , (String
"bytestring-encoding", VERSION_bytestring_encoding)
#endif
#ifdef VERSION_case_insensitive
  , (String
"case-insensitive", VERSION_case_insensitive)
#endif
#ifdef VERSION_clock
  , (String
"clock", VERSION_clock)
#endif
#ifdef VERSION_containers
  , (String
"containers", VERSION_containers)
#endif
#ifdef VERSION_data_default
  , (String
"data-default", VERSION_data_default)
#endif
#ifdef VERSION_data_default_class
  , (String
"data-default-class", VERSION_data_default_class)
#endif
#ifdef VERSION_data_interval
  , (String
"data-interval", VERSION_data_interval)
#endif
#ifdef VERSION_deepseq
  , (String
"deepseq", VERSION_deepseq)
#endif
#ifdef VERSION_directory
  , (String
"directory", VERSION_directory)
#endif
#ifdef VERSION_extended_reals
  , (String
"extended-reals", VERSION_extended_reals)
#endif
#ifdef VERSION_filepath
  , (String
"filepath", VERSION_filepath)
#endif
#ifdef VERSION_finite_field
  , (String
"finite-field", VERSION_finite_field)
#endif
#ifdef VERSION_ghc_prim
  , (String
"ghc-prim", VERSION_ghc_prim)
#endif
#ifdef VERSION_hashable
  , (String
"hashable", VERSION_hashable)
#endif
#ifdef VERSION_hashtables
  , (String
"hashtables", VERSION_hashtables)
#endif
#ifdef VERSION_haskeline
  , ("haskeline", VERSION_haskeline)
#endif
#ifdef VERSION_heaps
  , (String
"heaps", VERSION_heaps)
#endif
#ifdef VERSION_intern
  , (String
"intern", VERSION_intern)
#endif
#ifdef VERSION_lattices
  , (String
"lattices", VERSION_lattices)
#endif
#ifdef VERSION_log_domain
  , (String
"log-domain", VERSION_log_domain)
#endif
#ifdef VERSION_logic_TPTP
  , ("logic-TPTP", VERSION_logic_TPTP)
#endif
#ifdef VERSION_loop
  , (String
"loop", VERSION_loop)
#endif
#ifdef VERSION_megaparsec
  , (String
"megaparsec", VERSION_megaparsec)
#endif
#ifdef VERSION_mtl
  , (String
"mtl", VERSION_mtl)
#endif
#ifdef VERSION_multiset
  , (String
"multiset", VERSION_multiset)
#endif
#ifdef VERSION_mwc_random
  , (String
"mwc-random", VERSION_mwc_random)
#endif
#ifdef VERSION_optparse_applicative
  , ("optparse-applicative", VERSION_optparse_applicative)
#endif
#ifdef VERSION_parsec
  , ("parsec", VERSION_parsec)
#endif
#ifdef VERSION_pretty
  , (String
"pretty", VERSION_pretty)
#endif
#ifdef VERSION_primes
  , (String
"primes", VERSION_primes)
#endif
#ifdef VERSION_primitive
  , (String
"primitive", VERSION_primitive)
#endif
#ifdef VERSION_process
  , (String
"process", VERSION_process)
#endif
#ifdef VERSION_pseudo_boolean
  , (String
"pseudo-boolean", VERSION_pseudo_boolean)
#endif
#ifdef VERSION_queue
  , (String
"queue", VERSION_queue)
#endif
#ifdef VERSION_scientific
  , (String
"scientific", VERSION_scientific)
#endif
#ifdef VERSION_semigroups
  , (String
"semigroups", VERSION_semigroups)
#endif
#ifdef VERSION_sign
  , (String
"sign", VERSION_sign)
#endif
#ifdef VERSION_split
  , ("split", VERSION_split)
#endif
#ifdef VERSION_stm
  , (String
"stm", VERSION_stm)
#endif
#ifdef VERSION_template_haskell
  , (String
"template-haskell", VERSION_template_haskell)
#endif
#ifdef VERSION_temporary
  , (String
"temporary", VERSION_temporary)
#endif
#ifdef VERSION_text
  , (String
"text", VERSION_text)
#endif
#ifdef VERSION_time
  , (String
"time", VERSION_time)
#endif
#ifdef VERSION_transformers
  , (String
"transformers", VERSION_transformers)
#endif
#ifdef VERSION_transformers_compat
  , (String
"transformers-compat", VERSION_transformers_compat)
#endif
#ifdef VERSION_unbounded_delays
  , ("unbounded-delays", VERSION_unbounded_delays)
#endif
#ifdef VERSION_unordered_containers
  , (String
"unordered-containers", VERSION_unordered_containers)
#endif
#ifdef VERSION_vector
  , (String
"vector", VERSION_vector)
#endif
#ifdef VERSION_vector_space
  , (String
"vector-space", VERSION_vector_space)
#endif
#ifdef VERSION_xml_conduit
  , (String
"xml-conduit", VERSION_xml_conduit)
#endif
#ifdef VERSION_zlib
  , (String
"zlib", VERSION_zlib)
#endif
  ]

gitHash :: Maybe String
gitHash :: Maybe String
gitHash = $(gitHashQ)

compilationTime :: UTCTime
compilationTime :: UTCTime
compilationTime = $(compilationTimeQ)