{- Copyright (c) 2013, Alex Cole This Source Code Form is subject to the terms of the Mozilla Public License, v. 2.0. If a copy of the MPL was not distributed with this file, You can obtain one at http://mozilla.org/MPL/2.0/. -} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE EmptyDataDecls #-} {- # LANGUAGE KindSignatures #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} module Data.Types.Reorder.Base where import Language.Haskell.TH import GHC.TypeLits import Data.Constraint -- This is simply a placeholder to mark the end of our dynamic data type. data ReorderableEnd reorderableEnd :: ReorderableEnd reorderableEnd = undefined -- This determines the relative ordering of two types. Generally the first -- type given is either a concrete type or a container, and the second type is -- only a concrete type. If it isn't, then "TypeOrder_Composition" is used to -- indicate the special case and recurse. data TypeOrder_Lower data TypeOrder_Higher data TypeOrder_Same data TypeOrder_Composition data TypeOrder_End type family TypeOrder t0 t1 type instance TypeOrder ReorderableEnd ReorderableEnd = TypeOrder_End -- | Get the order of a new type relative to an existing collection of types, -- i.e. extract the top type in the collection and compare to that. The -- "GetReorderableChild" type doesn't actually need the last "x" type parameter. type family GetReorderableChild (container :: * -> * -> *) a x type instance GetReorderableChild container (container l r) x = r type instance GetReorderableChild container ReorderableEnd x = ReorderableEnd -- | Pass the container so we can pattern match on it at the type level. type GetTypeOrder container a t = TypeOrder (GetReorderableChild container a t) t class ReorderableInstance (a :: * -> Constraint) (n :: Nat) (r :: Symbol) | a n -> r