Code Monkey home page Code Monkey logo

tisch's Issues

Update tutorial to show how unHsR and runQueryMany fit together

I'm assuming from the types that the f passed to runQueryMany is supposed to be something like unHsR' however I can't make the type inference line up.

queryDb :: ( MonadReader Connection m, MonadIO m, MonadThrow m
           , PP.Default O.QueryRunner q r
           , Tabla t, UnHsR t a, PgR t ~ q, r ~ HsR t) => O.Query q -> m [a]
queryDb = runQueryMany (unHsR (T :: T t) )

(and many variations thereof) can seem to get the inference correct for Default.

This however:

main = do
  let con = (undefined :: Connection)
      m = runQueryMany (unHsR (T::T TTodoItem)) q -- :: m [TodoItem]
  (res :: [TodoItem]) <- runReaderT m con
  print res
  where
    q :: O.Query (PgR TTodoItem)
    q = queryTabla'

seems to be correct.

`Tutorial.hs` times out on CI

Tutorial.hs also takes a pretty long time for me locally (though not 10m; ~30s). I compiled with --ghc-options="-v2" and find that most of the time is spent by the simplifier:

[1 of 2] Compiling Tutorial         ( tests/Tutorial.hs, /Users/eeasley/code/tisch/dist-newstyle/build/x86_64-osx/ghc-8.2.1/tisch-0.1/c/tests/build/tests/tests-tmp/Tutorial.o )
*** Parser [Tutorial]:
!!! Parser [Tutorial]: finished in 7.52 milliseconds, allocated 14.747 megabytes
*** Renamer/typechecker [Tutorial]:
!!! Renamer/typechecker [Tutorial]: finished in 1296.85 milliseconds, allocated 772.685 megabytes
*** Desugar [Tutorial]:
Result size of Desugar (after optimization)
  = {terms: 4,639, types: 122,936, coercions: 783,558, joins: 0/104}
!!! Desugar [Tutorial]: finished in 772.89 milliseconds, allocated 806.432 megabytes
*** Simplifier [Tutorial]:
Result size of Simplifier iteration=1
  = {terms: 9,734,
     types: 234,812,
     coercions: 1,522,157,
     joins: 0/295}
Result size of Simplifier iteration=2
  = {terms: 6,067, types: 83,236, coercions: 644,374, joins: 0/77}
Result size of Simplifier iteration=3
  = {terms: 5,942, types: 81,222, coercions: 623,726, joins: 0/81}
Result size of Simplifier iteration=4
  = {terms: 5,932, types: 81,150, coercions: 623,726, joins: 0/76}
Result size of Simplifier
  = {terms: 5,932, types: 81,150, coercions: 623,726, joins: 0/76}
!!! Simplifier [Tutorial]: finished in 2690.53 milliseconds, allocated 2485.835 megabytes
*** Specialise [Tutorial]:
Result size of Specialise
  = {terms: 7,095, types: 88,099, coercions: 695,247, joins: 0/73}
!!! Specialise [Tutorial]: finished in 95.52 milliseconds, allocated 40.302 megabytes
*** Float out(FOS {Lam = Just 0,
                   Consts = True,
                   OverSatApps = False}) [Tutorial]:
Result size of Float out(FOS {Lam = Just 0,
                              Consts = True,
                              OverSatApps = False})
  = {terms: 8,916, types: 115,897, coercions: 695,247, joins: 0/18}
!!! Float out(FOS {Lam = Just 0,
                   Consts = True,
                   OverSatApps = False}) [Tutorial]: finished in 349.35 milliseconds, allocated 51.536 megabytes
*** Simplifier [Tutorial]:
Result size of Simplifier iteration=1
  = {terms: 8,133, types: 92,204, coercions: 702,085, joins: 9/44}
Result size of Simplifier iteration=2
  = {terms: 7,614, types: 90,194, coercions: 678,471, joins: 8/17}
Result size of Simplifier iteration=3
  = {terms: 7,583, types: 90,145, coercions: 678,439, joins: 7/13}
Result size of Simplifier
  = {terms: 7,583, types: 90,145, coercions: 678,439, joins: 7/13}
!!! Simplifier [Tutorial]: finished in 3206.89 milliseconds, allocated 3472.791 megabytes
*** Simplifier [Tutorial]:
Result size of Simplifier iteration=1
  = {terms: 7,144, types: 89,542, coercions: 678,428, joins: 7/13}
Result size of Simplifier
  = {terms: 6,806, types: 89,042, coercions: 678,428, joins: 7/13}
!!! Simplifier [Tutorial]: finished in 1060.88 milliseconds, allocated 955.829 megabytes
*** Simplifier [Tutorial]:
Result size of Simplifier iteration=1
  = {terms: 24,584,
     types: 324,021,
     coercions: 4,296,656,
     joins: 8/1,944}
Result size of Simplifier iteration=2
  = {terms: 26,232,
     types: 282,953,
     coercions: 3,986,583,
     joins: 7/1,446}
Result size of Simplifier iteration=3
  = {terms: 21,169,
     types: 229,973,
     coercions: 3,903,227,
     joins: 14/678}
Result size of Simplifier iteration=4
  = {terms: 20,921,
     types: 229,112,
     coercions: 3,882,558,
     joins: 9/638}
Result size of Simplifier
  = {terms: 20,921,
     types: 229,112,
     coercions: 3,882,558,
     joins: 9/638}
!!! Simplifier [Tutorial]: finished in 12859.28 milliseconds, allocated 14800.715 megabytes
*** Float inwards [Tutorial]:
Result size of Float inwards
  = {terms: 20,921,
     types: 229,112,
     coercions: 3,882,558,
     joins: 9/638}
!!! Float inwards [Tutorial]: finished in 131.01 milliseconds, allocated 54.599 megabytes
*** Called arity analysis [Tutorial]:
Result size of Called arity analysis
  = {terms: 20,921,
     types: 229,112,
     coercions: 3,882,558,
     joins: 9/638}
!!! Called arity analysis [Tutorial]: finished in 97.26 milliseconds, allocated 35.778 megabytes
*** Simplifier [Tutorial]:
Result size of Simplifier iteration=1
  = {terms: 20,900,
     types: 226,034,
     coercions: 3,882,935,
     joins: 9/635}
Result size of Simplifier iteration=2
  = {terms: 20,842,
     types: 224,932,
     coercions: 3,882,195,
     joins: 7/628}
Result size of Simplifier
  = {terms: 20,842,
     types: 224,932,
     coercions: 3,882,195,
     joins: 7/628}
!!! Simplifier [Tutorial]: finished in 4743.34 milliseconds, allocated 4272.203 megabytes
*** Demand analysis [Tutorial]:
Result size of Demand analysis
  = {terms: 20,842,
     types: 224,932,
     coercions: 3,882,195,
     joins: 7/628}
!!! Demand analysis [Tutorial]: finished in 366.63 milliseconds, allocated 119.349 megabytes
*** Worker Wrapper binds [Tutorial]:
Result size of Worker Wrapper binds
  = {terms: 21,617,
     types: 226,597,
     coercions: 3,882,225,
     joins: 7/728}
!!! Worker Wrapper binds [Tutorial]: finished in 92.08 milliseconds, allocated 14.379 megabytes
*** Simplifier [Tutorial]:
Result size of Simplifier iteration=1
  = {terms: 21,570,
     types: 226,461,
     coercions: 3,882,766,
     joins: 15/721}
Result size of Simplifier iteration=2
  = {terms: 21,084,
     types: 225,467,
     coercions: 3,882,185,
     joins: 7/628}
Result size of Simplifier
  = {terms: 21,084,
     types: 225,467,
     coercions: 3,882,185,
     joins: 7/628}
!!! Simplifier [Tutorial]: finished in 4362.12 milliseconds, allocated 4272.406 megabytes
*** Float out(FOS {Lam = Just 0,
                   Consts = True,
                   OverSatApps = True}) [Tutorial]:
Result size of Float out(FOS {Lam = Just 0,
                              Consts = True,
                              OverSatApps = True})
  = {terms: 22,034,
     types: 229,733,
     coercions: 3,882,185,
     joins: 7/614}
!!! Float out(FOS {Lam = Just 0,
                   Consts = True,
                   OverSatApps = True}) [Tutorial]: finished in 251.40 milliseconds, allocated 166.737 megabytes
*** Common sub-expression [Tutorial]:
Result size of Common sub-expression
  = {terms: 15,573,
     types: 160,572,
     coercions: 1,069,329,
     joins: 7/614}
!!! Common sub-expression [Tutorial]: finished in 180.11 milliseconds, allocated 64.582 megabytes
*** Float inwards [Tutorial]:
Result size of Float inwards
  = {terms: 15,573,
     types: 160,572,
     coercions: 1,069,329,
     joins: 7/614}
!!! Float inwards [Tutorial]: finished in 83.45 milliseconds, allocated 33.625 megabytes
*** Simplifier [Tutorial]:
Result size of Simplifier iteration=1
  = {terms: 14,705,
     types: 155,869,
     coercions: 1,093,171,
     joins: 7/613}
Result size of Simplifier iteration=2
  = {terms: 14,610,
     types: 155,574,
     coercions: 1,084,813,
     joins: 7/603}
Result size of Simplifier
  = {terms: 14,610,
     types: 155,574,
     coercions: 1,084,813,
     joins: 7/603}
!!! Simplifier [Tutorial]: finished in 1978.67 milliseconds, allocated 1877.248 megabytes
*** Demand analysis [Tutorial]:
Result size of Demand analysis
  = {terms: 14,610,
     types: 155,574,
     coercions: 1,084,813,
     joins: 7/603}
!!! Demand analysis [Tutorial]: finished in 163.62 milliseconds, allocated 77.471 megabytes
*** CoreTidy [Tutorial]:
Result size of Tidy Core
  = {terms: 13,638,
     types: 150,245,
     coercions: 1,070,992,
     joins: 7/592}
!!! CoreTidy [Tutorial]: finished in 330.62 milliseconds, allocated 187.693 megabytes
Created temporary directory: /var/folders/51/hc2gn2z15037t3zj4x5vvd3w0000gp/T/ghc55035_0
*** CorePrep [Tutorial]:
Result size of CorePrep
  = {terms: 17,729,
     types: 200,188,
     coercions: 1,070,992,
     joins: 7/2,219}
!!! CorePrep [Tutorial]: finished in 136.86 milliseconds, allocated 45.787 megabytes
*** Stg2Stg:
*** CodeGen [Tutorial]:
!!! CodeGen [Tutorial]: finished in 829.13 milliseconds, allocated 961.995 megabytes
*** Assembler:
*** Deleting temp files:
Warning: deleting non-existent /var/folders/51/hc2gn2z15037t3zj4x5vvd3w0000gp/T/ghc55035_0/ghc_3.c
Warning: deleting non-existent /var/folders/51/hc2gn2z15037t3zj4x5vvd3w0000gp/T/ghc55035_0/ghc_1.s
compile: input file tests/Main.hs
*** Checking old interface for Main (use -ddump-hi-diffs for more details):

Roadmap for hackage release?

I would just like to ask what the authors thoughts are for what remains to be done before this can be on hackage. Can you highlight any of the existing issues that need to be addressed? Are there some which are not listed? I'd like to start contributing in whatever direction will lead to this if I can.

Alternative to OverloadedLabels?

I'm going through the tutorial module, and there's somewhat heavy usage of OverloadedLabels in the code that makes compiles really slow for me (similar to the case with gi-gtk). Is there an alternative (I'm willing to endure some boilerplate/prefixed record selector names/etc.) to this?

Using generic-lens might be an option: it supports things like label @"foo" using nothing but GHC.Generics, which greatly cuts down on the compile-time overhead without sacrificing any type safety. However, from my limited experience with tisch, I'm not sure how the type/data family techniques used here will interact with generic programming. (What would you even derive Generic for?)

Edit: I've found the IsLabel instances (!) which showed me what I wanted to be doing instead (in this case, something like view (col (Proxy @Foo))). Even then, I'm interested in whether there's a lower-friction API possible using generics.

Insert for readonly

Is it possible to provide a RO which will always use the default to build HsI values? I ask because I'd like to make any id columns readonly, such as:

type instance Columns User =
   '[ 'Column "id" RO R UserId UserId
    , 'Column "name" W R PGText Text
    , ...

but then I can't make an insert with just the other fields using mkHsI:

ghci
:t mkHsI User
mkHsI User
  :: Tagged "id" (TypeError ...)
    -> Tagged "name" Text
    ->  ...

I'd like to have

ghci
:t mkHsI User
mkHsI User
  :: Tagged "name" Text
    ->  ...

where the id would always just use WDef automatically.

For now I just leave RO as WD and provide WDef in mkHsI. This functionality would just make things a slight bit tidier.

I may be missing something, I only discovered this library today after reading this fantastic blog post: http://ren.zone/articles/opaleye-sot.

PgRN null column

I'm having an issue where one of the columns in my table is nullable. I do a left join and end up with a PgRN value in my query. When I run the query, if the value of that column is null, it sets the whole record as Nothing.

Tag database connections with `Database`

I'm working on a pretty large code base split between two postgres databases, and I'm kind of wishing that the connection was also tagged with a database so that it's impossible to use it in a runQuery where it doesn't make sense. for example, the type signature of runQuery would become

-- | Query and fetch zero or more resulting rows.
runQuery
 :: (MonadIO m, Cx.MonadThrow m, PP.Default O.QueryRunner v r, Allow 'Fetch ps)
 => Conn ps d -> Query d () v -> m [r] -- ^

what are the authors' views on this?

Single column table definition fails to compile.

Given the following definition.

type instance Columns ThingTable =
  [ 'Column "id"           'WD 'R  PGInt4        ThingId
  ]

The following compilation error results.

src/Database/Internal/Thing.hs:41:3: error:
    • Expected kind '[Column
                        ghc-prim-0.5.0.0:GHC.Types.Symbol
                        WCap
                        RCap
                        ghc-prim-0.5.0.0:GHC.Types.Type
                        ghc-prim-0.5.0.0:GHC.Types.Type]',
        but '['Column "id" 'WD 'R PGInt4 ThingId]' has kind '*'
    • In the type '[Column "id" WD R PGInt4 ThingId]'
      In the type instance declaration for 'Columns'

src/Database/Internal/Thing.hs:41:5: error:
    • Expected a type, but
      ''Column "id" 'WD 'R PGInt4 ThingId' has kind
      'Column ghc-prim-0.5.0.0:GHC.Types.Symbol WCap RCap * *'
    • In the type '[Column "id" WD R PGInt4 ThingId]'
      In the type instance declaration for 'Columns'

Adding a second column to the definition as below resolves the error.

type instance Columns ThingTable =
  [ 'Column "id"           'WD 'R  PGInt4        ThingId
  , 'Column "name"         'W  'R  PGText        ThingName
  ]

Add support for built-in range types

Tisch doesn't seem to have support for range types

I'm not versed in Tisch's internals, but adding the following code:

import           Data.Time               (Day, LocalTime, UTCTime)
import           Opaleye.PGTypes         (PGRange)
import           Tisch.Internal.Kol      (PgPrimType (..))

instance PgTyped (PGRange PGTimestamptz) where type PgType (PGRange PGTimestamptz) = PGRange PGTimestamptz
instance PgTyped (PGRange PGTimestamp) where type PgType (PGRange PGTimestamp) = PGRange PGTimestamp
instance PgTyped (PGRange (PGNumeric s)) where type PgType (PGRange (PGNumeric s)) = PGRange (PGNumeric s)
instance PgTyped (PGRange PGInt4) where type PgType (PGRange PGInt4) = PGRange PGInt4
instance PgTyped (PGRange PGInt8) where type PgType (PGRange PGInt8) = PGRange PGInt8
instance PgTyped (PGRange PGDate) where type PgType (PGRange PGDate) = PGRange PGDate

instance PgPrimType (PGRange PGTimestamptz) where pgPrimTypeName _ = "tstzrange"
instance PgPrimType (PGRange PGTimestamp) where pgPrimTypeName _ = "tsrange"
instance PgPrimType (PGRange (PGNumeric s)) where pgPrimTypeName _ = "numrange"
instance PgPrimType (PGRange PGInt4) where pgPrimTypeName _ = "int4range"
instance PgPrimType (PGRange PGInt8) where pgPrimTypeName _ = "int8range"
instance PgPrimType (PGRange PGDate) where pgPrimTypeName _ = "daterange"

seems to make the following column compile:

'Column "duration" 'WD 'RN (PGRange PGTimestamptz) (PGRange UTCTime)

(still haven't tested the above code)

Documentation for mkHsI out of date

Example of use still refers to the old type class method:

Helper function to safely build an HsI t.

The type of this function isn't easy to understand, but an example should clarify its usage. We will asume we have a TPerson which is an instance of Table, and Person datatype as follows:

data TPerson

instance Table TPerson where
data T TPerson = TPerson
type Database TPerson = ... not important ...
type SchemaName TPerson = ... not important ...
type TableName TPerson = ... not important ...
type Columns TPerson
= '[ 'Col "name" W R PGText Text
, 'Col "age" W R PGInt4 Int32
]

data Person = Person
{ _personName :: Text
, _personAge :: Int
}
With that in place, and with the OverloadedLabels GHC extension enabled, we can use mkHsI as follows:

personToHsI :: Person -> HsI TPerson
personToHsI person =
mkHsI TPerson
(hsi #name (_personName person))
(hsi #age (_personAge age))

Add support for DISTINCT ON

We have distinct, we should have distinctOn as well. In fact, we probably should have just one distinct like this:

distinct :: PP.Default OI.Distinctspec b b => (a -> b) -> Query d () a -> Query d () a

leftJoin returning Nothing for right hand table (PgRN)

leftJoins appear to always return Nothing for the right hand table. For example, in this query:

queryById :: FeatureId -> Query Db1 () (PgR FeatureTable, PgRN FV.VersionTable)
queryById fid = proc () -> do
  (a, b) <- leftJoin
    (query FeatureTable) (query FV.VersionTable)
    (\f v -> eq (#id f) (#feature_id v)) -< ()
  restrict -< eq (#id a) (kol . untag $ fid)
  returnA -< (a, b)

Called here:

fetchById
  :: (MonadIO m, MonadThrow m)
  => FeatureId -> Conn' Db1 -> ExceptT QueryError m FeatureReadable
fetchById fid conn =
  runQuery conn (queryById fid) >>= \r -> do
    traceShowM r

A trace if the result shows:

[(HsR {unHsR = RCons (Tagged (Tagged 1)) (RCons (Tagged (Tagged "things")) (RCons (Tagged (Tagged 2017-11-22 02:29:46.473068 UTC)) (RNil)))},Nothing),(HsR {unHsR = RCons (Tagged (Tagged 1)) (RCons (Tagged (Tagged "things")) (RCons (Tagged (Tagged 2017-11-22 02:29:46.473068 UTC)) (RNil)))},Nothing),(HsR {unHsR = RCons (Tagged (Tagged 1)) (RCons (Tagged (Tagged "things")) (RCons (Tagged (Tagged 2017-11-22 02:29:46.473068 UTC)) (RNil)))},Nothing)]

Which corresponds to the 3 results I should be getting from the leftJoin, however the right side is Nothing. I did some digging and turned query logging on and the query being generated is as follows:

SELECT "result1_0_3" as "result1_4",
	        "result1_1_3" as "result2_4",
	        "result1_2_3" as "result3_4",
	        "result2_0_3" as "result4_4",
	        "result2_1_3" as "result5_4",
	        "result2_2_3" as "result6_4",
	        "result2_3_3" as "result7_4",
	        "result2_4_3" as "result8_4",
	        "result2_5_3" as "result9_4",
	        "result2_6_3" as "result10_4",
	        "result2_7_3" as "result11_4",
	        "result2_8_3" as "result12_4"
	 FROM (SELECT *
	       FROM (SELECT *
	             FROM
	            (SELECT "id0_1" as "result1_0_3",
	                     "name1_1" as "result1_1_3",
	                     "created_date2_1" as "result1_2_3",
	                     *
	              FROM (SELECT *
	                    FROM (SELECT "id" as "id0_1",
	                                 "name" as "name1_1",
	                                 "created_date" as "created_date2_1"
	                          FROM "public"."feature" as "T1") as "T1") as "T1") as "T1"
	             LEFT OUTER JOIN
	            (SELECT "feature_id0_2" as "result2_0_3",
	                     "version_number1_2" as "result2_1_3",
	                     "version_status2_2" as "result2_2_3",
	                     "allow_internal_users3_2" as "result2_3_3",
	                     "created_date4_2" as "result2_4_3",
	                     "private_preview_date5_2" as "result2_5_3",
	                     "public_preview_date6_2" as "result2_6_3",
	                     "public_date7_2" as "result2_7_3",
	                     "core_date8_2" as "result2_8_3",
	                     *
	              FROM (SELECT *
	                    FROM (SELECT "feature_id" as "feature_id0_2",
	                                 "version_number" as "version_number1_2",
	                                 "version_status" as "version_status2_2",
	                                 "allow_internal_users" as "allow_internal_users3_2",
	                                 "created_date" as "created_date4_2",
	                                 "private_preview_date" as "private_preview_date5_2",
	                                 "public_preview_date" as "public_preview_date6_2",
	                                 "public_date" as "public_date7_2",
	                                 "core_date" as "core_date8_2"
	                          FROM "public"."feature_version" as "T1") as "T1") as "T1") as "T2"
	             ON
	             ("id0_1") = ("feature_id0_2")) as "T1"
	       WHERE (("result1_0_3") = 1)) as "T1";

Which when run manually returns the expected results:

 result1_4 | result2_4 |           result3_4           | result4_4 | result5_4 | result6_4 | result7_4 |           result8_4           | result9_4 | result10_4 | result11_4 | result12_4 
-----------+-----------+-------------------------------+-----------+-----------+-----------+-----------+-------------------------------+-----------+------------+------------+------------
         1 | things    | 2017-11-22 02:29:46.473068+00 |         1 |         1 |         0 |           | 2017-11-22 21:49:48.955197+00 |           |            |            | 
         1 | things    | 2017-11-22 02:29:46.473068+00 |         1 |         2 |         0 |           | 2017-11-22 22:04:41.536123+00 |           |            |            | 
         1 | things    | 2017-11-22 02:29:46.473068+00 |         1 |         3 |         0 |           | 2017-11-22 22:23:53.527832+00 |           |            |            | 
(3 rows)

Direct queries of the right hand table and innerJoins work without issue.

This looks like it may be related to #37

CC @boj

Is this a sane implementation with Data.Tagged?

Rather than:

newtype Code = Code { unCode :: Text }
    deriving (Show, Eq, Generic)
instance ToJSON Code
instance FromJSON Code
instance Wrapped Code where
  type Unwrapped Code = Text
  _Wrapped' = iso unCode Code
instance PgTyped Code where
  type PgType Code = PGText
instance ToKol Code Code
instance PgEq Code
instance QueryRunnerColumnDefault PGText Code where
  queryRunnerColumnDefault = qrcWrapped

I was experimenting with this since you seem to get quite a bit for free:

data CodeTag
type Code = Tagged CodeTag Text

mkCode :: Text -> Code
mkCode = Tagged

instance PgTyped Code where
  type PgType Code = PGText
instance PgEq Code
instance QueryRunnerColumnDefault PGText Code where
  queryRunnerColumnDefault = qrcWrapped

Which required this change:

-- from
type instance Columns CodeTable =
  [ 'Column "code" 'W  'R  Code Code ]

-- to
type instance Columns CodeTable =
  [ 'Column "code" 'W  'R  PGText Code ]

My queries, HsR/PgR/etc. conversions, and the like all work as intended. Is something lost in this case by using PGText on the PostgreSQL side here? (I could not get the Code Code instance to compile correctly, which lead me to my current solution).

Question about mkHsI

Hi,

I like the new API, seem a lot more straightforward!

I'm looking at the writing side of things now, but I'm unsure what columns I need to supply for the mkHsI function. I assumed it's just the 'W columns, with the 'WD columns being optional so given

data TTodoItem
instance Tabla TTodoItem where
  type Database TTodoItem = TodoDb
  type SchemaName TTodoItem = "todo"
  type TableName TTodoItem = "todo_item"
  type Cols TTodoItem =
    [ 'Col "id" 'WD 'R O.PGUuid TodoItemId
    , 'Col "title" 'W 'R O.PGText Text
    , 'Col "created" 'WD 'R O.PGTimestamptz UTCTime
    , 'Col "due" 'WD 'RN O.PGTimestamptz UTCTime
    , 'Col "completed" 'WD 'RN O.PGTimestamptz UTCTime
    ]

I had expected this:

mkHsI (T :: T TTodoItem) $ \set_ -> hBuild
    (set_ (C :: C "title") t) -- t :: Text
    (set_ (C :: C "due") mDue) -- mDue :: (Maybe UTCTime)

to be sufficient.

However I get:

    Couldn't match type '[y,
                           Tagged (TC TTodoItem "due") (Maybe UTCTime),
                           Tagged (TC TTodoItem "title") Text]
                   with '[]
    arising from a functional dependency between:
      constraint HRevApp
                    '[]
                    '[Tagged (TC TTodoItem "due") (Maybe UTCTime),
                      Tagged (TC TTodoItem "title") Text, y,
                      Tagged (TC TTodoItem "due") (Maybe UTCTime),
                      Tagged (TC TTodoItem "title") Text]
                    '[Tagged (TC TTodoItem "due") (Maybe UTCTime),
                      Tagged (TC TTodoItem "title") Text]
        arising from a use of hBuild
      instance HRevApp '[] l2 l2 at <no location info>
    In the expression:
      hBuild (set_ (C :: C "title") t) (set_ (C :: C "due") mDue)
    In the second argument of ($), namely
      ‘\ set_
         -> hBuild (set_ (C :: C "title") t) (set_ (C :: C "due") mDue)
    In the expression:
      mkHsI (T :: T TTodoItem)
      $ \ set_
          -> hBuild (set_ (C :: C "title") t) (set_ (C :: C "due") mDue)

I haven't been able to work my way through the types to understand what this is telling me yet.

Cheers!

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.