{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.Ninja.IR.Pool
(
Pool, makePool, makePoolDefault, makePoolConsole, makePoolCustom
, poolName, poolDepth
, PoolName, makePoolNameDefault, makePoolNameConsole, makePoolNameCustom
, _PoolNameDefault, _PoolNameConsole, _PoolNameCustom
, poolNameText, printPoolName, parsePoolName
, PoolDepth
, makePoolDepth, makePoolInfinite
, poolDepthPositive
) where
import Control.Applicative (empty)
import qualified Control.Lens as Lens
import Data.Aeson ((.:), (.=))
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Types as Aeson
import Data.Text (Text)
import qualified Data.Text as Text
import Control.DeepSeq (NFData)
import Data.Hashable (Hashable)
import Data.String (IsString (fromString))
import GHC.Generics (Generic)
import Test.SmallCheck.Series ((<~>), (\/))
import qualified Test.SmallCheck.Series as SC
import qualified Language.Ninja.Misc.Positive as Misc
import Flow ((.>), (|>))
data Pool
= MkPool
{ _poolName :: !PoolName
, _poolDepth :: !PoolDepth
}
deriving (Eq, Ord, Show, Read, Generic)
{-# INLINEABLE makePool #-}
makePool :: PoolName -> PoolDepth -> Maybe Pool
makePool PoolNameDefault PoolInfinite = Just makePoolDefault
makePool PoolNameConsole (PoolDepth 1) = Just makePoolConsole
makePool (PoolNameCustom t) (PoolDepth d) = if d >= 1
then Just (makePoolCustom t d)
else Nothing
makePool _ _ = Nothing
{-# INLINE makePoolDefault #-}
makePoolDefault :: Pool
makePoolDefault = MkPool makePoolNameDefault PoolInfinite
{-# INLINE makePoolConsole #-}
makePoolConsole :: Pool
makePoolConsole = MkPool makePoolNameConsole (PoolDepth 1)
{-# INLINE makePoolCustom #-}
makePoolCustom :: Text
-> Misc.Positive
-> Pool
makePoolCustom name depth = MkPool (makePoolNameCustom name) (PoolDepth depth)
{-# INLINE poolName #-}
poolName :: Lens.Getter Pool PoolName
poolName = Lens.to _poolName
{-# INLINE poolDepth #-}
poolDepth :: Lens.Getter Pool PoolDepth
poolDepth = Lens.to _poolDepth
instance Aeson.ToJSON Pool where
toJSON (MkPool {..})
= [ "name" .= _poolName
, "depth" .= _poolDepth
] |> Aeson.object
instance Aeson.FromJSON Pool where
parseJSON = (Aeson.withObject "Pool" $ \o -> do
_poolName <- (o .: "name") >>= pure
_poolDepth <- (o .: "depth") >>= pure
pure (MkPool {..}))
instance forall m. (Monad m, SC.Serial m Text) => SC.Serial m Pool where
series = pure makePoolDefault
\/ pure makePoolConsole
\/ (let nameSeries :: SC.Series m Text
nameSeries = SC.series >>= (\case "" -> empty
"console" -> empty
x -> pure x)
in makePoolCustom <$> nameSeries <~> SC.series)
instance (Monad m, SC.CoSerial m Text) => SC.CoSerial m Pool where
coseries = SC.coseries .> fmap (\f -> convert .> f)
where
convert :: Pool -> (PoolName, PoolDepth)
convert pool = (Lens.view poolName pool, Lens.view poolDepth pool)
instance Hashable Pool
instance NFData Pool
data PoolName
= PoolNameDefault
| PoolNameConsole
| PoolNameCustom !Text
deriving (Eq, Ord, Show, Read, Generic)
{-# INLINE makePoolNameDefault #-}
makePoolNameDefault :: PoolName
makePoolNameDefault = PoolNameDefault
{-# INLINE makePoolNameConsole #-}
makePoolNameConsole :: PoolName
makePoolNameConsole = PoolNameConsole
{-# INLINEABLE makePoolNameCustom #-}
makePoolNameCustom :: Text -> PoolName
makePoolNameCustom "" = error "Invalid pool name: \"\""
makePoolNameCustom "console" = error "Invalid pool name: \"console\""
makePoolNameCustom text = PoolNameCustom text
{-# INLINE _PoolNameDefault #-}
_PoolNameDefault :: Lens.Getter PoolName (Maybe ())
_PoolNameDefault = Lens.to (\case PoolNameDefault -> Just ()
_ -> Nothing)
{-# INLINE _PoolNameConsole #-}
_PoolNameConsole :: Lens.Getter PoolName (Maybe ())
_PoolNameConsole = Lens.to (\case PoolNameConsole -> Just ()
_ -> Nothing)
{-# INLINE _PoolNameCustom #-}
_PoolNameCustom :: Lens.Getter PoolName (Maybe Text)
_PoolNameCustom = Lens.to (\case (PoolNameCustom t) -> Just t
_ -> Nothing)
{-# INLINE poolNameText #-}
poolNameText :: Lens.Iso' PoolName Text
poolNameText = Lens.iso printPoolName parsePoolName
{-# INLINEABLE printPoolName #-}
printPoolName :: PoolName -> Text
printPoolName PoolNameDefault = ""
printPoolName PoolNameConsole = "console"
printPoolName (PoolNameCustom t) = t
{-# INLINEABLE parsePoolName #-}
parsePoolName :: Text -> PoolName
parsePoolName "" = makePoolNameDefault
parsePoolName "console" = makePoolNameConsole
parsePoolName t = makePoolNameCustom t
instance IsString PoolName where
fromString = Text.pack .> parsePoolName
instance Aeson.ToJSON PoolName where
toJSON = printPoolName .> Aeson.String
instance Aeson.FromJSON PoolName where
parseJSON = Aeson.withText "PoolName" (parsePoolName .> pure)
instance Aeson.ToJSONKey PoolName where
toJSONKey = Aeson.toJSONKeyText printPoolName
instance Aeson.FromJSONKey PoolName where
fromJSONKey = Aeson.mapFromJSONKeyFunction parsePoolName Aeson.fromJSONKey
instance (Monad m, SC.Serial m Text) => SC.Serial m PoolName where
series = parsePoolName <$> (pure "" \/ pure "console" \/ SC.series)
instance (Monad m, SC.CoSerial m Text) => SC.CoSerial m PoolName where
coseries = SC.coseries
.> fmap (\f -> printPoolName .> f)
instance Hashable PoolName
instance NFData PoolName
data PoolDepth
= PoolDepth !Misc.Positive
| PoolInfinite
deriving (Eq, Ord, Show, Read, Generic)
{-# INLINE makePoolDepth #-}
makePoolDepth :: Misc.Positive -> PoolDepth
makePoolDepth = PoolDepth
{-# INLINE makePoolInfinite #-}
makePoolInfinite :: PoolDepth
makePoolInfinite = PoolInfinite
{-# INLINE poolDepthPositive #-}
poolDepthPositive :: Lens.Iso' PoolDepth (Maybe Misc.Positive)
poolDepthPositive = Lens.iso fromPD toPD
where
{-# INLINE fromPD #-}
fromPD :: PoolDepth -> Maybe Misc.Positive
fromPD (PoolDepth p) = Just p
fromPD PoolInfinite = Nothing
{-# INLINE toPD #-}
toPD :: Maybe Misc.Positive -> PoolDepth
toPD (Just p) = PoolDepth p
toPD Nothing = PoolInfinite
instance Aeson.ToJSON PoolDepth where
toJSON (PoolDepth i) = Aeson.toJSON i
toJSON PoolInfinite = "infinite"
instance Aeson.FromJSON PoolDepth where
parseJSON (v@(Aeson.Number _)) = PoolDepth <$> Aeson.parseJSON v
parseJSON (Aeson.String "infinite") = pure PoolInfinite
parseJSON owise = Aeson.typeMismatch "PoolDepth" owise
instance (Monad m) => SC.Serial m PoolDepth where
series = pure PoolInfinite
\/ (SC.series |> fmap PoolDepth)
instance (Monad m) => SC.CoSerial m PoolDepth where
coseries = SC.coseries
.> fmap (\f -> \case (PoolDepth i) -> f (Just i)
PoolInfinite -> f Nothing)
instance Hashable PoolDepth
instance NFData PoolDepth