aboutsummaryrefslogtreecommitdiffstats
path: root/Database.hs
blob: 87670c43e1aa78db1be1b113551a632cb2ed47a0 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Database
    ( Database(..)
    , lookup
    , readFile
    )
  where

import Prelude hiding (lookup,readFile)
import qualified Prelude (readFile)

import Data.Data
import Data.IxSet.Typed
import Network.DNS.Types

deriving instance Data OData
deriving instance Data Question
deriving instance Data RData
deriving instance Data ResourceRecord
deriving instance Data TYPE
deriving instance Ord Question
deriving instance Ord ResourceRecord
deriving instance Ord TYPE
deriving instance Read OData
deriving instance Read Question
deriving instance Read RData
deriving instance Read ResourceRecord

type ResourceRecordIxs = '[Domain, TYPE]
type IxResourceRecord = IxSet ResourceRecordIxs ResourceRecord
data Database = Database
    { recordSet :: IxResourceRecord
    }
  deriving (Read,Show)

instance Indexable ResourceRecordIxs ResourceRecord where
  indices = ixList
              (ixGen (Proxy :: Proxy Domain))
              (ixGen (Proxy :: Proxy TYPE))

lookup :: Question -> Database -> [ResourceRecord]
lookup Question{..} (Database ix) =
  toList (ix @= qname @= qtype)

readFile :: FilePath -> IO Database
readFile path =
  read <$> Prelude.readFile path