Skip to content

Instantly share code, notes, and snippets.

@nc6
Last active August 29, 2017 10:05
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 nc6/256171a95618b16b99c4bdbc4ee332f5 to your computer and use it in GitHub Desktop.
Save nc6/256171a95618b16b99c4bdbc4ee332f5 to your computer and use it in GitHub Desktop.
{-
I have a type as the following:
```data Foo =
Foo1 (Either String Int)
| Foo2 (Either String Char)
| Foo3 (Either String Bar)
...
```
There may end up being a lot of these. All will have `Either String a` inside. There are a bunch of functions taking a `Foo` argument. In most cases, the behaviour of how to treat a `Left` is the same, but for one, where it's important to know the constructor. I can't thus pull the `Either` out to the top level. Nor can I easily just turn the constructor into a tag, because it determines the type inside the `Right`
Am I missing a nice way to structure this?
-}
{-# LANGUAGE TypeFamilies, DataKinds, GADTs, TemplateHaskell #-}
import Data.Singletons
import Data.Singletons.TH
data Tag = Tag1 | Tag2 | Tag3
type family Foo (x :: Tag) :: * where
Foo 'Tag1 = Int
Foo Tag2 = Char
Foo Tag3 = Int
data Bar = forall (a :: Tag). Bar (Sing a) (Either String (Foo a))
$(genSingletons [''Tag])
bar = Bar (sing :: Sing Tag1) (Right 1)
bar2 = Bar (sing :: Sing Tag2) (Left "hsidoh")
consumeLefts :: Bar -> Maybe String
consumeLefts (Bar _ (Left a)) = Just a
consumeLefts _ = Nothing
consumeLeftsCare :: Bar -> String
consumeLeftsCare (Bar STag1 _) = "tag1"
consumeLeftsCare _ = "not tag1"
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment