summaryrefslogtreecommitdiff
path: root/Biz/Id.hs
blob: 344149dc50cc928b54bfdaa07f242996147a8de4 (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
54
55
56
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- Integer-based identifier.
module Biz.Id
  ( Id (..),
    mk,
    untag,
  )
where

import Alpha
import Data.Aeson (FromJSON (..), ToJSON (..))
import Data.Binary (Binary)
import Data.Data (Data)
import Servant (FromHttpApiData (..), ToHttpApiData (..))

newtype Id entity = Id Int
  deriving (Eq, Ord, Show, Generic, Typeable, Data)

mk :: proxy entity -> Int -> Id entity
mk _ = Id

untag :: Id entity -> Int
untag (Id i) = i

instance Hashable (Id entity)

instance Binary (Id entity)

instance Enum (Id entity) where
  toEnum = mk (Proxy :: Proxy entity)
  fromEnum = untag

instance NFData (Id entity) where
  rnf (Id s) = rnf s

instance FromJSON (Id entity) where
  parseJSON = fmap Id <. parseJSON

instance ToJSON (Id entity) where
  toJSON = toJSON <. untag

-- this is just provided to satisfy Monoid, no reason to actually use it
instance Semigroup (Id entity) where
  a <> b = mk (Proxy :: Proxy entity) <| untag a + untag b

instance Monoid (Id entity) where
  mempty = mk (Proxy :: Proxy entity) 0

instance FromHttpApiData (Id entity) where
  parseUrlPiece p = mk (Proxy :: Proxy entity) </ parseUrlPiece p

instance ToHttpApiData (Id entity) where
  toUrlPiece p = untag p |> tshow