{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ConstraintKinds #-}
module Data.TypedEncoding.Common.Types.Common where
import Data.TypedEncoding.Common.Util.TypeLits
import GHC.TypeLits
type EncAnn = String
type Restriction s = (KnownSymbol s, IsR s ~ 'True)
type EncodingAnn s = (KnownSymbol s, IsEnc s ~ 'True)
type Algorithm nm alg = AlgNm nm ~ alg
type family AlgNm (encnm :: Symbol) :: Symbol where
AlgNm encnm = TakeUntil encnm ":"
type family AlgNmMap (nms :: [Symbol]) :: [Symbol] where
AlgNmMap '[] = '[]
AlgNmMap (x ': xs) = AlgNm x ': AlgNmMap xs
type family IsR (s :: Symbol) :: Bool where
IsR s = AcceptEq ('Text "Not restriction encoding " ':<>: ShowType s ) (CmpSymbol "r-" (Take 2 s))
type family IsROrEmpty (s :: Symbol) :: Bool where
IsROrEmpty "" = True
IsROrEmpty x = IsR x
type family RemoveRs (s :: [Symbol]) :: [Symbol] where
RemoveRs '[] = '[]
RemoveRs (x ': xs) = If (OrdBool (CmpSymbol "r-" (Take 2 x))) (RemoveRs xs) (x ': RemoveRs xs)
type family IsEnc (s :: Symbol) :: Bool where
IsEnc s = AcceptEq ('Text "Not enc- encoding " ':<>: ShowType s ) (CmpSymbol "enc-" (Take 4 s))