{-# LANGUAGE DeriveDataTypeable, DeriveGeneric, GeneralizedNewtypeDeriving, TemplateHaskell #-}
module Data.UserId where
import Control.Applicative ((<$>))
import Data.Aeson (FromJSON(..), ToJSON(..), Result(..), fromJSON)
import Data.Data (Data)
import Data.SafeCopy (SafeCopy, base, deriveSafeCopy)
import Data.Serialize (Serialize)
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Text.Boomerang.TH (makeBoomerangs)
import Web.Routes (PathInfo(..))
import Web.Routes.TH (derivePathInfo)
newtype UserId = UserId { UserId -> Integer
_unUserId :: Integer }
deriving (UserId -> UserId -> Bool
(UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool) -> Eq UserId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserId -> UserId -> Bool
== :: UserId -> UserId -> Bool
$c/= :: UserId -> UserId -> Bool
/= :: UserId -> UserId -> Bool
Eq, Eq UserId
Eq UserId =>
(UserId -> UserId -> Ordering)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool)
-> (UserId -> UserId -> UserId)
-> (UserId -> UserId -> UserId)
-> Ord UserId
UserId -> UserId -> Bool
UserId -> UserId -> Ordering
UserId -> UserId -> UserId
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: UserId -> UserId -> Ordering
compare :: UserId -> UserId -> Ordering
$c< :: UserId -> UserId -> Bool
< :: UserId -> UserId -> Bool
$c<= :: UserId -> UserId -> Bool
<= :: UserId -> UserId -> Bool
$c> :: UserId -> UserId -> Bool
> :: UserId -> UserId -> Bool
$c>= :: UserId -> UserId -> Bool
>= :: UserId -> UserId -> Bool
$cmax :: UserId -> UserId -> UserId
max :: UserId -> UserId -> UserId
$cmin :: UserId -> UserId -> UserId
min :: UserId -> UserId -> UserId
Ord, Int -> UserId
UserId -> Int
UserId -> [UserId]
UserId -> UserId
UserId -> UserId -> [UserId]
UserId -> UserId -> UserId -> [UserId]
(UserId -> UserId)
-> (UserId -> UserId)
-> (Int -> UserId)
-> (UserId -> Int)
-> (UserId -> [UserId])
-> (UserId -> UserId -> [UserId])
-> (UserId -> UserId -> [UserId])
-> (UserId -> UserId -> UserId -> [UserId])
-> Enum UserId
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: UserId -> UserId
succ :: UserId -> UserId
$cpred :: UserId -> UserId
pred :: UserId -> UserId
$ctoEnum :: Int -> UserId
toEnum :: Int -> UserId
$cfromEnum :: UserId -> Int
fromEnum :: UserId -> Int
$cenumFrom :: UserId -> [UserId]
enumFrom :: UserId -> [UserId]
$cenumFromThen :: UserId -> UserId -> [UserId]
enumFromThen :: UserId -> UserId -> [UserId]
$cenumFromTo :: UserId -> UserId -> [UserId]
enumFromTo :: UserId -> UserId -> [UserId]
$cenumFromThenTo :: UserId -> UserId -> UserId -> [UserId]
enumFromThenTo :: UserId -> UserId -> UserId -> [UserId]
Enum, ReadPrec [UserId]
ReadPrec UserId
Int -> ReadS UserId
ReadS [UserId]
(Int -> ReadS UserId)
-> ReadS [UserId]
-> ReadPrec UserId
-> ReadPrec [UserId]
-> Read UserId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UserId
readsPrec :: Int -> ReadS UserId
$creadList :: ReadS [UserId]
readList :: ReadS [UserId]
$creadPrec :: ReadPrec UserId
readPrec :: ReadPrec UserId
$creadListPrec :: ReadPrec [UserId]
readListPrec :: ReadPrec [UserId]
Read, Int -> UserId -> ShowS
[UserId] -> ShowS
UserId -> String
(Int -> UserId -> ShowS)
-> (UserId -> String) -> ([UserId] -> ShowS) -> Show UserId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserId -> ShowS
showsPrec :: Int -> UserId -> ShowS
$cshow :: UserId -> String
show :: UserId -> String
$cshowList :: [UserId] -> ShowS
showList :: [UserId] -> ShowS
Show, Typeable UserId
Typeable UserId =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UserId -> c UserId)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UserId)
-> (UserId -> Constr)
-> (UserId -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UserId))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserId))
-> ((forall b. Data b => b -> b) -> UserId -> UserId)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> UserId -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> UserId -> r)
-> (forall u. (forall d. Data d => d -> u) -> UserId -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> UserId -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId)
-> Data UserId
UserId -> Constr
UserId -> DataType
(forall b. Data b => b -> b) -> UserId -> UserId
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> UserId -> u
forall u. (forall d. Data d => d -> u) -> UserId -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UserId
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UserId -> c UserId
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UserId)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserId)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UserId -> c UserId
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> UserId -> c UserId
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UserId
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c UserId
$ctoConstr :: UserId -> Constr
toConstr :: UserId -> Constr
$cdataTypeOf :: UserId -> DataType
dataTypeOf :: UserId -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UserId)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c UserId)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserId)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UserId)
$cgmapT :: (forall b. Data b => b -> b) -> UserId -> UserId
gmapT :: (forall b. Data b => b -> b) -> UserId -> UserId
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UserId -> r
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> UserId -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> UserId -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UserId -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> UserId -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> UserId -> m UserId
Data, Typeable, (forall x. UserId -> Rep UserId x)
-> (forall x. Rep UserId x -> UserId) -> Generic UserId
forall x. Rep UserId x -> UserId
forall x. UserId -> Rep UserId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UserId -> Rep UserId x
from :: forall x. UserId -> Rep UserId x
$cto :: forall x. Rep UserId x -> UserId
to :: forall x. Rep UserId x -> UserId
Generic, Get UserId
Putter UserId
Putter UserId -> Get UserId -> Serialize UserId
forall t. Putter t -> Get t -> Serialize t
$cput :: Putter UserId
put :: Putter UserId
$cget :: Get UserId
get :: Get UserId
Serialize)
deriveSafeCopy 1 'base ''UserId
unUserId :: (Integer -> f Integer) -> UserId -> f UserId
unUserId Integer -> f Integer
f (UserId Integer
x) = (Integer -> UserId) -> f Integer -> f UserId
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> UserId
UserId (Integer -> f Integer
f Integer
x)
{-# INLINE unUserId #-}
makeBoomerangs ''UserId
instance ToJSON UserId where toJSON :: UserId -> Value
toJSON (UserId Integer
i) = Integer -> Value
forall a. ToJSON a => a -> Value
toJSON Integer
i
instance FromJSON UserId where parseJSON :: Value -> Parser UserId
parseJSON Value
v = Integer -> UserId
UserId (Integer -> UserId) -> Parser Integer -> Parser UserId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Integer
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
instance PathInfo UserId where
toPathSegments :: UserId -> [Text]
toPathSegments (UserId Integer
i) = Integer -> [Text]
forall url. PathInfo url => url -> [Text]
toPathSegments Integer
i
fromPathSegments :: URLParser UserId
fromPathSegments = Integer -> UserId
UserId (Integer -> UserId)
-> ParsecT [Text] () Identity Integer -> URLParser UserId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Text] () Identity Integer
forall url. PathInfo url => URLParser url
fromPathSegments
succUserId :: UserId -> UserId
succUserId :: UserId -> UserId
succUserId (UserId Integer
i) = Integer -> UserId
UserId (Integer -> Integer
forall a. Enum a => a -> a
succ Integer
i)