{-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} -- | -- Copyright : Anders Claesson 2015, 2016 -- Maintainer : Anders Claesson -- License : BSD-3 -- module HOPS.DB ( DB (..), Sequences , readSeqDB , readANumDB , emptyANumDB ) where import Control.Applicative import GHC.TypeLits import Data.Proxy import Data.Vector (Vector) import qualified Data.Vector as V import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as B import System.Directory import HOPS.GF.Series import HOPS.OEIS import HOPS.Config -- | An empty data declaration used with the phantom `DB` data type. data Sequences -- | A data base (DB) is just a wrapped `ByteString`. newtype DB a = DB {unDB :: ByteString} deriving Show -- | Read the DB at the given location. readDB :: FilePath -> IO (DB a) readDB fpath = doesFileExist fpath >>= \b -> if b then DB <$> B.readFile fpath else error "No local A-number database; run 'hops --update' first." -- | Read the sequence DB (derived from \"stripped.gz\"). readSeqDB :: Config -> IO (DB Sequences) readSeqDB = readDB . seqDBPath -- | Create a vector that at index 'n' contains the sequence with -- A-number 'n'. readANumDB :: KnownNat n => Config -> IO (Vector (Series n)) readANumDB cfg = let mkSeries = series (Proxy :: Proxy n) . map Val . snd in V.fromList . map mkSeries . parseStripped . unDB <$> readSeqDB cfg -- | An empty A-number database emptyANumDB :: KnownNat n => Vector (Series n) emptyANumDB = V.empty