Skip to content

Instantly share code, notes, and snippets.

@thoferon
Last active December 20, 2015 09:30
Show Gist options
  • Save thoferon/6108295 to your computer and use it in GitHub Desktop.
Save thoferon/6108295 to your computer and use it in GitHub Desktop.
Quick test with dependent types in Haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
data Confidence = High | Medium | Low deriving (Show, Eq)
data Dataset :: Confidence -> * -> * where
Dataset :: [a] -> Dataset c a
type family MinConfidence (c1 :: Confidence) (c2 :: Confidence) :: Confidence
type instance MinConfidence High c = c
type instance MinConfidence Medium High = Medium
type instance MinConfidence Medium Medium = Medium
type instance MinConfidence Medium Low = Low
type instance MinConfidence Low c = Low
combine :: Dataset c1 a -> Dataset c2 a -> Dataset (MinConfidence c1 c2) a
combine (Dataset l1) (Dataset l2) = Dataset $ l1 ++ l2
--------------------------------------------------------------------------
data CProxy :: Confidence -> * where
CProxy :: CProxy c
class ToConfidence (c :: Confidence) where
toConfidence :: CProxy c -> Confidence
instance ToConfidence High where toConfidence _ = High
instance ToConfidence Medium where toConfidence _ = Medium
instance ToConfidence Low where toConfidence _ = Low
getConfidence :: ToConfidence c => Dataset c a -> Confidence
getConfidence (_ :: Dataset c a) = toConfidence (CProxy :: CProxy c)
--------------------------------------------------------------------------
instance (ToConfidence c, Show a) => Show (Dataset c a) where
show (d :: Dataset c a) =
let confidence = getConfidence d
Dataset list = d
in show list ++ " (with confidence: " ++ show confidence ++ ")"
--------------------------------------------------------------------------
d1 :: Dataset Low Int
d1 = Dataset [1, 2]
d2 :: Dataset Medium Int
d2 = Dataset [2, 3]
d3 :: Dataset High Int
d3 = Dataset [3, 4]
main :: IO ()
main = do
print d1
print d3
print $ combine d1 d2
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment