predicate-typed-0.6.0.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Util_TH

Contents

Description

Template Haskell methods for creating Refined, Refined2, and Refined3 refinement types

Synopsis

Refined

refinedTH :: forall p i. (Lift i, RefinedC p i) => i -> Q (TExp (Refined p i)) Source #

creates a Refined refinement type with terse output

>$$(refinedTH 123) :: Refined (Between 100 125 Id) Int
Refined {unRefined = 123}
it :: Refined (Between 100 125 Id) Int
>$$(refinedTH 99) :: Refined (Between 100 125 Id) Int

interactive:8:4: error:
    * refinedTH: predicate failed with FalseP (100 <= 99)
    * In the Template Haskell splice $$(refinedTH 99)
      In the expression:
          $$(refinedTH 99) :: Refined (Between 100 125 Id) Int
      In an equation for 'it':
          it = $$(refinedTH 99) :: Refined (Between 100 125 Id) Int

refinedTH' :: forall p i. (Lift i, RefinedC p i) => POpts -> i -> Q (TExp (Refined p i)) Source #

creates a Refined refinement type

allows you to specify display options (eg ou for unicode / o2 for ansi)

>$$(refinedTH' o2 123) :: Refined (Between 100 125 Id) Int
Refined {unRefined = 123}
it :: Refined (Between 100 125 Id) Int
>$$(refinedTH' o2 99) :: Refined (FailS "asdf" >> Between 100 125 Id) Int

interactive:116:4: error:
    *
[Error asdf] lhs failed >>
|
`- [Error asdf] Fail asdf
   |
   `- P 'asdf

refinedTH: predicate failed with FailP "asdf" ((>>) lhs failed)
    * In the Template Haskell splice $$(refinedTH' o0 99)
      In the expression:
          $$(refinedTH' o2 99) ::
            Refined (FailS "asdf" >> Between 100 125 Id) Int

Refined2

refined2TH :: forall ip op i. (Show (PP ip i), Lift i, Lift (PP ip i), Refined2C ip op i) => i -> Q (TExp (Refined2 ip op i)) Source #

creates a Refined2 refinement type with terse output

>$$(refined2TH 100) :: Refined2 Id (Between 100 125 Id) Id Int
Refined2 {r2In = 100, r2Out = 100}

refined2TH' :: forall ip op i. (Show (PP ip i), Lift i, Lift (PP ip i), Refined2C ip op i) => POpts -> i -> Q (TExp (Refined2 ip op i)) Source #

creates a Refined2 refinement type

allows you to specify display options (eg ou for unicode / o2 for ansi)

>$$(refined2TH' o2 100) :: Refined2 Id (Between 100 125 Id) Int
Refined2 {r2In = 100, r2Out = 100}
>$$(refined2TH' o2 99) :: Refined2 Id (Between 100 125 Id) Int

interactive:127:4: error:
    *
*** Step 1. Success Initial Conversion(ip) [99] ***

P Id 99

*** Step 2. False Boolean Check(op) ***

False 100 <= 99
|
+- P Id 99
|
+- P '100
|
`- P '125

refined2TH: predicate failed with Step 2. False Boolean Check(op) | {100 <= 99}
    * In the Template Haskell splice $$(refined2TH' o2 99)
      In the expression:
          $$(refined2TH' o2 99) :: Refined2 Id (Between 100 125 Id) Id Int
      In an equation for 'it':
          it = $$(refined2TH' o2 99) :: Refined2 Id (Between 100 125 Id) Id Int

Refined3

refined3TH :: forall ip op fmt i. (Show i, Show (PP ip i), Lift i, Lift (PP ip i), Refined3C ip op fmt i) => i -> Q (TExp (Refined3 ip op fmt i)) Source #

creates a Refined3 refinement type with terse output

>$$(refined3TH 100) :: Refined3 Id (Between 100 125 Id) Id Int
Refined3 {r3In = 100, r3Out = 100}

refined3TH' :: forall ip op fmt i. (Show i, Show (PP ip i), Lift i, Lift (PP ip i), Refined3C ip op fmt i) => POpts -> i -> Q (TExp (Refined3 ip op fmt i)) Source #

creates a Refined3 refinement type

allows you to specify display options (eg ou for unicode / o2 for ansi)

>$$(refined3TH' o2 100) :: Refined3 Id (Between 100 125 Id) Id Int
Refined3 {r3In = 100, r3Out = 100}
>$$(refined3TH' o2 99) :: Refined3 Id (Between 100 125 Id) Id Int

interactive:127:4: error:
    *
*** Step 1. Success Initial Conversion(ip) [99] ***

P Id 99

*** Step 2. False Boolean Check(op) ***

False 100 <= 99
|
+- P Id 99
|
+- P '100
|
`- P '125

refined3TH: predicate failed with Step 2. False Boolean Check(op) | {100 <= 99}
    * In the Template Haskell splice $$(refined3TH' o2 99)
      In the expression:
          $$(refined3TH' o2 99) :: Refined3 Id (Between 100 125 Id) Id Int
      In an equation for 'it':
          it = $$(refined3TH' o2 99) :: Refined3 Id (Between 100 125 Id) Id Int