Skip to content

Instantly share code, notes, and snippets.

@patrickt
Created February 4, 2020 21:00
Show Gist options
  • Star 1 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save patrickt/1dc0e6267d5d950db44c2dc862ca10e5 to your computer and use it in GitHub Desktop.
Save patrickt/1dc0e6267d5d950db44c2dc862ca10e5 to your computer and use it in GitHub Desktop.
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Data.Some
( Some (..)
, Some1 (..)
, Any
) where
import Data.Aeson
import Data.Kind
data Some (c :: Type -> Constraint) where
Some :: c a => a -> Some c
instance ToJSON (Some ToJSON) where
toJSON (Some a) = toJSON a
toEncoding (Some a) = toEncoding a
data Some1 (c :: (Type -> Type) -> Constraint) (d :: Type -> Constraint) where
Some1 :: forall c d f a . (c f, d a) => f a -> Some1 c d
instance ToJSON (Some1 ToJSON1 ToJSON) where
toJSON (Some1 fa) = toJSON1 fa
toEncoding (Some1 fa) = toEncoding1 fa
-- To wrap a GADT, partially apply (~) to get a constraint. If you have no
-- constraints on the inner item, use the Any typeclass.
-- e.g. if you had data SomeGADT = SomeGADT (forall a . MyGADT a)
-- you can replace it with Some1 ((~) MyGADT) Any
class Any x
instance Any x
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment