Skip to content

Instantly share code, notes, and snippets.

@takoeight0821
Last active December 2, 2019 07:08
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save takoeight0821/a4447fff1cb20966c778b1e662053b36 to your computer and use it in GitHub Desktop.
Save takoeight0821/a4447fff1cb20966c778b1e662053b36 to your computer and use it in GitHub Desktop.
generic 'if'
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RebindableSyntax #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
module GIf where
import Data.Kind
import GHC.Generics
import Prelude
class GIf f where
gIfThenElse :: f p -> b -> b -> b
ifThenElse :: (GIf (Rep a), Generic a) => a -> b -> b -> b
ifThenElse c = gIfThenElse (from c)
instance NotSum b => GIf (a :+: b) where
gIfThenElse (L1 _) _ x = x
gIfThenElse (R1 _) x _ = x
instance (GIf (Rep c), Generic c) => GIf (K1 i c) where
gIfThenElse (K1 x) = ifThenElse x
instance GIf f => GIf (M1 i t f) where
gIfThenElse (M1 x) = gIfThenElse x
class NotSum (f :: k -> Type)
instance NotSum V1
instance NotSum U1
instance NotSum (a :*: b)
instance NotSum (K1 i c)
instance NotSum f => NotSum (M1 i t f)
example1 :: Bool
example1 = (if True then 1 else 2) == 1
example2 :: Bool
example2 = (if Nothing then 1 else 2) == 2
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment