{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Type.Regex.ListUtils -- Copyright : (C) 2016 Csongor Kiss -- License : BSD3 -- Maintainer : Csongor Kiss -- Stability : experimental -- Portability : non-portable -- -- Various auixiliary type families that operate on type-level lists. -- Cherry picked from Data.List and lifted to the type-level. -- ----------------------------------------------------------------------------- module Data.Type.Regex.ListUtils ( type Nub , type IsNull , type FilterOut , type Elem , type (++) ) where -- |Analogous to Data.List.nub type family Nub (xs :: [k]) :: [k] where Nub '[] = '[] Nub (x ': xs) = x ': Nub (FilterOut x xs) -- |Analogous to Data.List.null type family IsNull xs where IsNull '[] = 'True IsNull xs = 'False -- |Analogous to `Data.List.filter (/= x) xs` type family FilterOut (x :: k) (xs :: [k]) :: [k] where FilterOut x '[] = '[] FilterOut x (x ': xs) = FilterOut x xs FilterOut x (y ': xs) = y ': FilterOut x xs -- |Analogous to Data.List.elem type family Elem (x :: k) (xs :: [k]) where Elem x '[] = 'False Elem x (x ': xs) = 'True Elem x (y ': xs) = Elem x xs -- |Analogous to Data.List.++ type family xs ++ ys where '[] ++ ys = ys (x ': xs) ++ ys = x ': (xs ++ ys)