-- | Indicate that something is `Allocated`. module NewtypeZoo.Allocated ( Allocated(Allocated) , _theAllocated , theAllocated ) where import Control.Comonad (Comonad) import Control.DeepSeq (NFData) import Control.Monad.Fix (MonadFix) import Control.Monad.Zip (MonadZip) import Data.Bits (Bits,FiniteBits) import Data.Copointed (Copointed) import Data.Default (Default) import Data.Functor.Classes (Eq1, Ord1, Read1, Show1) import Data.Functor.Identity import Data.Ix (Ix) import Data.Profunctor (Profunctor, dimap) import Data.Pointed (Pointed) import Data.String (IsString) import Data.Typeable (Typeable) import Foreign.Storable (Storable) import GHC.Generics (Generic, Generic1) import System.Random (Random) import Test.QuickCheck (Arbitrary) -- | A wrapper for something that is `Allocated`. newtype Allocated a = Allocated a deriving ( Eq , Ord , Read , Show , NFData , Foldable , Traversable , Functor , Default , Monoid , Semigroup , Typeable , Generic , Generic1 , Random , Arbitrary , Bounded , Enum , Floating , Fractional , Integral , Num , Real , RealFloat , RealFrac , Ix , IsString , Bits , FiniteBits ) deriving ( Eq1 , Ord1 , Read1 , Show1 , Pointed , Copointed , Applicative , MonadFix , Monad , MonadZip , Comonad ) via Identity -- | An accessor function for something 'Allocated'. _theAllocated :: Allocated x -> x _theAllocated (Allocated !x) = x {-# INLINE _theAllocated #-} -- | A lens for something 'Allocated'. theAllocated :: forall a b p f. (Profunctor p, Functor f) => p a (f b) -> p (Allocated a) (f (Allocated b)) theAllocated = dimap _theAllocated (fmap Allocated) {-# INLINE theAllocated #-}