Skip to content

Commit

Permalink
[#45] Add newtype Id with phantom type parameter
Browse files Browse the repository at this point in the history
Resolves #45
  • Loading branch information
rashadg1030 committed Jun 19, 2019
1 parent 3b481ba commit 20f4cce
Show file tree
Hide file tree
Showing 5 changed files with 46 additions and 2 deletions.
2 changes: 2 additions & 0 deletions issue-wanted.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,9 @@ library
IW.Config

-- Core Modules
IW.Core.Id
IW.Core.Issue
IW.Core.Repo

-- Database
IW.Db
Expand Down
26 changes: 26 additions & 0 deletions src/IW/Core/Id.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,26 @@
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}

{-# LANGUAGE AllowAmbiguousTypes #-}

module IW.Core.Id
( Id (..)
, AnyId
, castId
) where

import Data.Type.Equality (type (==))


-- | Wrapper for integer id. Contains phantom type parameter for increased
-- type-safety.
newtype Id a = Id { unId :: Int }
deriving stock (Show, Generic)
deriving newtype (Eq, Ord, FromField, ToField, FromJSON, ToJSON)

-- | When we don't care about type of 'Id' but don't want to deal with type variables.
type AnyId = Id ()

-- | Unsafe cast of 'Id'. Implementation uses smart trick to enforce usage
-- always with @TypeApplications@.
castId :: forall to from to' . ((to == to') ~ 'True) => Id from -> Id to'
castId (Id a) = Id a
8 changes: 6 additions & 2 deletions src/IW/Core/Issue.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,15 +3,19 @@
module IW.Core.Issue
( Issue (..)
) where

import IW.Core.Id (Id)
import IW.Core.Repo (Repo)


-- | Data type representing a GitHub issue.
data Issue = Issue
{ issueId :: Int
{ issueId :: Id Issue
, issueNumber :: Int
, issueTitle :: Text
, issueBody :: Text
, issueUrl :: Text
, issueRepoId :: Int
, issueRepoId :: Id Repo
} deriving stock (Generic, Show, Eq)
deriving anyclass (FromRow, ToRow)
deriving (FromJSON, ToJSON)
11 changes: 11 additions & 0 deletions src/IW/Core/Repo.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
{-# LANGUAGE DeriveAnyClass #-}

module IW.Core.Repo
( Repo (..)
) where

import IW.Core.Id (Id)


-- | Data type representing a GitHub repository.
data Repo = Repo
1 change: 1 addition & 0 deletions src/IW/Db/Issue.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@ module IW.Db.Issue
( getIssues
, getIssueById
, getIssuesByLabel
, insertIssues
) where

import IW.App (WithError)
Expand Down

0 comments on commit 20f4cce

Please sign in to comment.