-- | This tutorial describes how to use the basic library.
--   Usually you would use the functions provided in the Internal.Data.Basic.TH module (re-exported
--   by Data.Basic) to generate all of the declarations in this tutorial from your database schema.
--
--   Basic is a database-first library meaning the schema comes from the database instead of your
--   code. The library provides mechanisms for "explaining" your schema to the compiler. It can
--   then use this information to provide a typesafe and convenient access and control of your data.
--
--   We start by defining a data type.
--
--  @
--  data User = User { _serId   :: 'Key'
--                   , _serName :: 'Text' } deriving ('Eq', 'Ord', 'Read', 'Show')
--  @
--
--   Most of the functionality is implemented through lenses so we need to generate them for our
--   datatype.
--
--  @
--  'makeLenses' ''User
--  @
--
--   Next we provide a set of instances for our type. These describe how our type maps to a database
--   table. We use type level strings to represent database names of the fields. Instances are
--   needed for each field and for each constraint on the table. We also need a 'FromRow' instance
--   so the type can actually be deserialized from the query result.
--
--  @
--  instance 'Table' User where
--      -- the database name for this table
--      type 'TableName' User = "blog_user"
--
--      -- a type level list of all the fields in this table
--      type 'TableFields' User = ["id", "name"]
--
--      -- a type level list of constraints on this table; each of these will need a corresponding
--      -- instance that provides additional info
--      type 'TableConstraints' User = '[ \''Unique' "blog_user_pkey"]
--
--      -- the table can optionally have a primary key; for this we use a type level 'Maybe' value
--      type 'TablePrimaryKey' User = \''Just' "blog_user_pkey"
--
--      -- a type level list of fields that are either 'Required' or 'DynamicDefault'
--      type 'TableRequiredFields' User = [\''Required' "id", \''Required' "name"]
--
--      -- a default user
--      -- don't worry about undefined values, the types will make sure you can't accidentally evaluate
--      -- them
--      'newEntity' = 'Entity' (User 'undefined' 'undefined')
--
--  instance 'UniqueConstraint' "blog_user_pkey" where
--      -- the table which this constraint targets
--      type 'UniqueTable' "blog_user_pkey" = User
--
--      -- you can have multiple fields that make up one unique constraint
--      type 'UniqueFields' "blog_user_pkey" = '["id"]
--
--  -- 'PrimaryKeyConstraint' is really just a synonym for a unique constraint + the condition that
--  -- all the values must not be null
--  instance 'PrimaryKeyConstraint' "blog_user_pkey"
--
--  -- each field gets an instance saying what Haskell type it maps to and providing a lens
--  instance 'TableField' User "id" where
--      type 'TableFieldType' User "id" = 'Key'
--      'tableFieldLens' = serId
--
--  instance 'TableField' User "name" where
--      type 'TableFieldType' User "name" = 'Text'
--      'tableFieldLens' = serName
--
--  instance 'FromRow' User where
--      'fromRow' = User '<$>' field '<*>' field
--  @
--
--   Now we do the same for a "blog_post" table.
--
--  @
--  data Post = Post { _ostId     :: 'Key'
--                   , _ostName   :: 'Text'
--                   , _ostUserId :: 'Key' } deriving ('Eq', 'Ord', 'Read', 'Show')
--
--  instance 'Table' Post where
--      type 'TableName' Post = "blog_post"
--      type 'TableFields' Post = ["id", "name", "author"]
--      type 'TableConstraints' Post = '[ \''ForeignKey' "blog_post_author_fkey"]
--      type 'TablePrimaryKey' Post = \''Just' "blog_post_pkey"
--      type 'TableRequiredFields' Post = [\''Required' "id", \''Required' "name", \''Required' "author"]
--      'newEntity' = 'Entity' (Post 'undefined' 'undefined')
--
--  instance 'UniqueConstraint' "blog_post_pkey" where
--      type 'UniqueTable' "blog_post_pkey" = Post
--      type 'UniqueFields' "blog_post_pkey" = '["id"]
--
--  instance 'PrimaryKeyConstraint' "blog_post_pkey"
--
--  instance 'FromRow' Post where
--      fromRow = Post '<$>' field '<*>' field '<*>' field
--  'makeLenses' ''Post
--
--  instance 'TableField' Post "id" where
--      type 'TableFieldType' Post "id" = 'Key'
--      'tableFieldLens' = ostId
--
--  instance 'TableField' Post "name" where
--      type 'TableFieldType' Post "name" = 'Text'
--      'tableFieldLens' = ostName
--
--  instance 'TableField' Post "author" where
--      type 'TableFieldType' Post "author" = 'Key'
--      'tableFieldLens' = ostUserId
--  @
--
--   Next, we declare a foreign key from the post table to the user table. The instance is more or
--   less self explanatory.
--
--  @
--  instance 'ForeignKeyConstraint' "blog_post_author_fkey" where
--      type 'ForeignKeyFrom' "blog_post_author_fkey" = Post
--      type 'ForeignKeyFromFields' "blog_post_author_fkey" = '["author"]
--      type 'ForeignKeyTo' "blog_post_author_fkey" = User
--      type 'ForeignKeyToFields' "blog_post_author_fkey" = '["id"]
--  @
--
--  Now we're ready to create the lenses and values that we'll use to manipulate our data.
--  Again, keep in mind that all of this can be generated for you via the TH functions, directly
--  from your SQL schema.
--
--  @
--  -- this value will represent a virtual "list" of all the users in the database
--  allUsers :: 'AllRows' User m r => m r
--  allUsers = 'allRows' @"blog_user"
--
--  -- this is the same, but for posts
--  allPosts :: 'AllRows' Post m r => m r
--  allPosts = 'allRows' @"blog_post"
--
--  -- we use this value to construct new users
--  newUser :: 'Entity' (\''Fresh' [\''Required' "id", \''Required' "name"]) User
--  newUser = 'newEntity'
--
--  newPost :: 'Entity' (\''Fresh' [\''Required' "id", \''Required' "name", \''Required' "author"]) Post
--  newPost = 'newEntity'
--
--  -- we can use this lens to get all posts belonging to some author
--  posts :: 'VirtualTable' "blog_post_author_fkey" m r
--        => 'Getter'\' ('Entity' (\''FromDb' c) ('ForeignKeyTo' "blog_post_author_fkey")) (m r)
--  posts = 'virtualTableLens' @"blog_post_author_fkey"
--
--  -- a lens to access the id field of any table that has it; same for name and authorId
--  id :: 'FieldOpticProxy' ('Proxy' "id" -> o) => o
--  id = 'fieldOptic' @"id"
--
--  name :: 'FieldOpticProxy' ('Proxy' "name" -> o) => o
--  name = 'fieldOptic' @"name"
--
--  authorId :: 'FieldOpticProxy' ('Proxy' "author" -> o) => o
--  authorId = 'fieldOptic' @"author"
--
--  -- this lens will let us get the actual user value from a post, through the foreign key
--  author :: 'ForeignKeyLensProxy' ('Proxy' "blog_post_author_fkey" -> o) => o
--  author = 'foreignKeyLens' @"blog_post_author_fkey"
--  @
--
--   Finally, we get to a usage example.
--
--  @
--  test1 :: ('MonadIO' m, 'MonadEffect' 'Basic' m) => m ()
--  test1 = do
--      'void' $ 'ddelete' allPosts
--      'void' $ 'ddelete' allUsers
--
--      -- we use the lens to construct values
--      let user = newUser '&' name '.~' "John"
--                         '&' id '.~' 1
--
--      -- check this out: try not setting one of the fields on user
--      -- the compiler will not let you insert the value into the database
--      user <- 'insert' user
--      let post = newPost '&' id '.~' 1
--                         '&' name '.~' "New post"
--                         '&' author '.~' user
--      post <- 'insert' post
--
--      -- to access our data we use functions like 'dfilter' and pretend we're dealing with
--      -- lists of values
--      users \<\- 'dfilter' (\\u -> (u '^.' id) `In` [1, 3, 4]) allUsers
--
--      -- get the author of a post, update the name and save it to the database
--      auth <- post '^.' author
--      'void' $ 'save' (auth '&' name '.~' "John H")
--
--      let user2 = newUser '&' name '.~' "Mike"
--                          '&' id '.~' 2
--      'void' $ 'insert' user2
--
--      -- sorting and taking works just like lists do, at least syntactically
--      -- the semantics still need to be translated to SQL so first taking, then sorting won't
--      -- compile
--      -- you can use the usual Down newtype for switching from ascending to descending
--      us \<\- 'dtake' 1 $ 'dsortOn' (\\u -> 'Down' (u '^.' id)) allUsers
--      'print' us
--
--      -- dupdate is like mapM
--      'void' $ 'dupdate' (\\u' -> u' '&' id '.~' (2 :: 'Key')) allUsers
--
--      [mike] \<\- 'dfilter' (\\u' -> u' '^.' id '==.' (1 :: 'Key')) allUsers
--      -- here we're using that special virtual table lens to get a list of all posts by Mike
--      psts <- mike '^.' posts
--      -- we can also filter on that list like it's a table in the database
--      somePsts \<\- dfilter (\\p -> p '^.' id '==.' (0 :: 'Key')) (mike '^.' posts)
--
--      -- joins are done with the djoin function; the resulting list can also be filtered
--      usersPosts <- allUsers `djoin` allPosts
--      print usersPosts
--
--  test :: 'IO' ()
--  test = do
--      conn <- 'connectPostgreSQL' "host=localhost port=5432 user=postgres dbname=postgres password=admin connect_timeout=10"
--      'handleBasicPsql' conn test1
--  @
{-# OPTIONS_GHC -Wno-unused-imports #-}
module Data.Basic.Tutorial where

import Internal.Interlude hiding (filter)

import Database.PostgreSQL.Simple hiding (In)
import Database.PostgreSQL.Simple.FromRow

import Internal.Data.Basic
import Internal.Data.Basic.Types
import Internal.Control.Effects.Basic
import Language.Haskell.TH