{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE LambdaCase #-} ----------------------------------------------------------------------------- -- | -- Module : Data.Type.Index.Quote -- Copyright : Copyright (C) 2015 Kyle Carter -- License : BSD3 -- -- Maintainer : Kyle Carter -- Stability : experimental -- Portability : RankNTypes -- -- A 'QuasiQuoter' for the 'Index' type. -- ----------------------------------------------------------------------------- module Data.Type.Index.Quote where import Data.Type.Index import Language.Haskell.TH import Language.Haskell.TH.Lib import Language.Haskell.TH.Quote import Text.Read (readMaybe) import Control.Monad ix :: QuasiQuoter ix = QuasiQuoter { quoteExp = parseIxExp , quotePat = parseIxPat , quoteType = error "ix: quoteType not defined" , quoteDec = error "ix: quoteDec not defined" } parseIxExp :: String -> Q Exp parseIxExp s = maybe (fail $ "ix: couldn't parse Int: " ++ show s) (notNeg >=> go) $ readMaybe s where notNeg :: Int -> Q Int notNeg n | n < 0 = fail $ "ix: negative index: " ++ show n | True = return n go :: Int -> Q Exp go = \case 0 -> [| IZ |] n -> [| IS $(go $ n-1) |] parseIxPat :: String -> Q Pat parseIxPat s = maybe (fail $ "ix: couldn't parse Int: " ++ show s) (notNeg >=> go) $ readMaybe s where notNeg :: Int -> Q Int notNeg n | n < 0 = fail $ "ix: negative index: " ++ show n | True = return n go :: Int -> Q Pat go = \case 0 -> [p| IZ |] n -> [p| IS $(go $ n-1) |]