Skip to content

Instantly share code, notes, and snippets.

@bolt12
Created March 24, 2020 20:41
Show Gist options
  • Save bolt12/812725ba23e88a753de60bd2fbb4781e to your computer and use it in GitHub Desktop.
Save bolt12/812725ba23e88a753de60bd2fbb4781e to your computer and use it in GitHub Desktop.
All possible inhabitants of a given type
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoStarIsType #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{- |
Copyright: (c) 2020 Armando Santos
SPDX-License-Identifier: MIT
Maintainer: Armando Santos <armandoifsantos@gmail.com>
A class that gives all inhabitants of a given type.
-}
module AllValuesPolished where
import GHC.Generics
class AllValues a where
allValues :: [a]
default allValues :: (Generic a, AllValues (Rep a R)) => [a]
allValues = map to (allValues @(Rep a R))
instance AllValues Char where
allValues = [minBound ..]
instance AllValues Bool where
allValues = [minBound ..]
instance AllValues Ordering where
allValues = [minBound ..]
instance (AllValues a, AllValues b) => AllValues (Either a b) where
allValues =
let as = map Left (allValues @a)
bs = map Right (allValues @b)
in as ++ bs
instance (AllValues a, AllValues b) => AllValues (a, b) where
allValues = (,) <$> allValues @a <*> allValues @b
instance (AllValues (f p)) => AllValues (M1 x y f p) where
allValues = map M1 (allValues @(f p))
instance AllValues c => AllValues (K1 x c y) where
allValues = map K1 (allValues @c)
instance AllValues (U1 x) where
allValues = [U1]
instance (AllValues (a p), AllValues (b p)) => AllValues ((:*:) a b p) where
allValues = (:*:) <$> allValues <*> allValues
instance (AllValues (a p), AllValues (b p)) => AllValues ((:+:) a b p) where
allValues =
let as = map L1 (allValues @(a p))
bs = map R1 (allValues @(b p))
in as ++ bs
data T = A Bool Bool | B | C deriving (Show, Generic)
instance AllValues T
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment