Skip to content

Commit

Permalink
universe-reverse-instances to not depend on universe-instances-base
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Jun 29, 2016
1 parent 4cb25e2 commit 58e176d
Show file tree
Hide file tree
Showing 9 changed files with 26 additions and 20 deletions.
26 changes: 14 additions & 12 deletions base/Data/Universe/Class.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,11 +2,17 @@
#ifdef DEFAULT_SIGNATURES
{-# LANGUAGE DefaultSignatures #-}
#endif
-- | Bottoms are ignored for this entire module: only fully-defined inhabitants
-- are considered inhabitants.
module Data.Universe.Class
( -- | Bottoms are ignored for this entire module: only fully-defined inhabitants are considered inhabitants.
(
-- * Classes
Universe(..)
, Finite(..)
, Univ(..)
, Univ
-- * Lists
, universe
, universeF
) where

import Data.Universe.Helpers
Expand All @@ -26,19 +32,15 @@ import Data.Universe.Helpers
-- in 'length' pfx = 'length' (nub pfx)
-- @
class Universe a where
-- | Memoised CAF. Use with care as the expanded value will live forever.
--
-- See <http://stackoverflow.com/questions/6090932/how-to-make-a-caf-not-a-caf-in-haskell>
universe :: [a]
universe = getUniv universeUniv

-- | 'Univ' containing all values of @a@.
universeUniv :: Univ a
#ifdef DEFAULT_SIGNATURES
default universeUniv :: (Enum a, Bounded a) => Univ a
universeUniv = universeDef
#endif

universe :: Universe a => [a]
universe = getUniv universeUniv

-- | Creating an instance of this class is a declaration that your 'universe'
-- eventually ends. Minimal definition: no methods defined. By default,
-- @universeF = universe@, but for some types (like 'Either') the 'universeF'
Expand All @@ -62,8 +64,8 @@ class Universe a where
-- Just 1
-- @
class Universe a => Finite a where
universeF :: [a]
universeF = getUniv universeUnivF

universeUnivF :: Univ a
universeUnivF = universeUniv

universeF :: Finite a => [a]
universeF = getUniv universeUnivF
3 changes: 2 additions & 1 deletion instances/base/tests/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,8 @@ module Main (main) where
import Data.List (elemIndex, nub)
import Data.Int (Int8)
import Test.QuickCheck
import Data.Universe.Instances.Base (Universe(..), Finite(..))
import Data.Universe.Class
import Data.Universe.Instances.Base ()

import qualified Data.Set as Set

Expand Down
3 changes: 2 additions & 1 deletion instances/containers/tests/Tests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,8 +3,9 @@ module Main (main) where

import Data.Set (Set)
import Test.QuickCheck
import Data.Universe.Class
import Data.Universe.Instances.Base ()
import Data.Universe.Instances.Containers (Universe(..), Finite(..))
import Data.Universe.Instances.Containers ()

import qualified Data.Set as Set

Expand Down
2 changes: 1 addition & 1 deletion instances/reverse/Data/Universe/Instances/Eq.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module Data.Universe.Instances.Eq (
Eq(..)
) where

import Data.Universe.Instances.Base
import Data.Universe.Class

instance (Finite a, Eq b) => Eq (a -> b) where
f == g = and [f x == g x | x <- universeF]
4 changes: 3 additions & 1 deletion instances/reverse/Data/Universe/Instances/Ord.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,10 @@ module Data.Universe.Instances.Ord (
Ord(..)
) where

import Data.Universe.Instances.Base
import Data.Monoid
import Data.Universe.Class
import Data.Universe.Instances.Eq ()
import Prelude

instance (Finite a, Ord b) => Ord (a -> b) where
f `compare` g = mconcat [f x `compare` g x | x <- universeF]
2 changes: 1 addition & 1 deletion instances/reverse/Data/Universe/Instances/Read.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ module Data.Universe.Instances.Read (
) where

import Data.Map (fromList, (!))
import Data.Universe.Instances.Base
import Data.Universe.Class

-- actually, the "Finite a" part of the context wouldn't be inferred if you
-- asked GHC -- but it's kind of hopeless otherwise!
Expand Down
2 changes: 1 addition & 1 deletion instances/reverse/Data/Universe/Instances/Show.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module Data.Universe.Instances.Show (
Show(..)
) where

import Data.Universe.Instances.Base
import Data.Universe.Class

instance (Finite a, Show a, Show b) => Show (a -> b) where
showsPrec n f = showsPrec n [(a, f a) | a <- universeF]
2 changes: 1 addition & 1 deletion instances/reverse/Data/Universe/Instances/Traversable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import Data.Foldable
import Data.Map ((!), fromList)
import Data.Monoid
import Data.Traversable
import Data.Universe.Instances.Base
import Data.Universe.Class
import Prelude

instance Finite e => Foldable ((->) e) where
Expand Down
2 changes: 1 addition & 1 deletion instances/reverse/universe-reverse-instances.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,6 @@ library
Data.Universe.Instances.Traversable
build-depends: base >=4 && <5 ,
containers >=0.4 && <0.6,
universe-instances-base >=2 && <3
universe-base >=2 && <3
default-language: Haskell2010
ghc-options: -Wall

0 comments on commit 58e176d

Please sign in to comment.