Skip to content

Commit

Permalink
Added CSS on login page
Browse files Browse the repository at this point in the history
  • Loading branch information
tusharad committed Sep 19, 2024
1 parent bceef33 commit e59fd61
Show file tree
Hide file tree
Showing 7 changed files with 95 additions and 16 deletions.
2 changes: 0 additions & 2 deletions haskread-platform-be/env.dhall
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,6 @@ let Env = {
mailAPIToken : Text,
mailFromEmail : Text,
oauth2Config : OAuth2Config,
jwtSecretKey_ : Text,
tokenExpiryTime : Natural -- Seconds
}

Expand All @@ -46,7 +45,6 @@ let env : Env = {
mailAPIToken = env:MailAPIToken as Text,
mailFromEmail = env:MailFromEmail as Text,
oauth2Config = oauth2Config,
jwtSecretKey_ = env:HaskReadJwtSecret as Text,
tokenExpiryTime = 3600 -- Seconds
}

Expand Down
1 change: 0 additions & 1 deletion haskread-platform-be/src/Platform/Common/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,6 @@ data Env = Env
mailAPIToken :: Text,
mailFromEmail :: Text,
oauth2Config :: OAuth2Config,
jwtSecretKey_ :: Text,
tokenExpiryTime :: Natural
}
deriving (Generic, FromDhall, Show)
Expand Down
2 changes: 1 addition & 1 deletion haskread-platform-be/src/Platform/Common/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,7 +155,7 @@ readEnv envFilePath = do
case ePool of
Left e -> pure $ Left $ toException e
Right pool -> do
let jwtSecretKey = fromSecret $ T.encodeUtf8 jwtSecretKey_
jwtSecretKey <- generateKey
loggerSet_ <- newFileLoggerSet defaultBufSize logFilePath
sem <- newQSem 10 -- 10 threads
let orvilleState = O.newOrvilleState O.defaultErrorDetailLevel pool
Expand Down
10 changes: 5 additions & 5 deletions haskread-platform-ui/src/Common/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,8 @@ module Common.Types
( BaseURL(..)
, ChangePasswordFields
, CommentInfo(..)
, Community(..)
, CommunityRep
, CreateThreadFields
, DeleteUserFields
, Endpoint(..)
Expand All @@ -10,6 +12,7 @@ module Common.Types
, NestedComment(..)
, OtpFields
, PaginatedArray
, Pagination(..)
, Profile
, RegisterFields
, RequestMethod(..)
Expand All @@ -18,23 +21,20 @@ module Common.Types
, ThreadInfo(..)
, ThreadRep
, Token(..)
, Community(..)
, CommunityRep
, UpdateThreadFields
, changePasswordCodec
, communitiesCodec
, createThreadCodec
, deleteUserCodec
, endpointCodec
, loginCodec
, myRoute
, nestedCommentsCodec
, profileCodec
, registerCodec
, threadCodec
, threadsCodec
, updateThreadCodec
, profileCodec
, communitiesCodec
, Pagination(..)
)
where

Expand Down
13 changes: 8 additions & 5 deletions haskread-platform-ui/src/Page/Home.purs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ import Prelude

import Bulma.CSS.Spacing as B
import Bulma.Columns.Columns as B
import Bulma.Columns.Size as B
import Bulma.Columns.Size hiding (isSmall) as B
import Bulma.Components.Pagination as B
import Bulma.Components.Tabs as B
import Bulma.Elements.Button as B
Expand Down Expand Up @@ -163,17 +163,20 @@ threadPreview _ thread =

paginationView :: forall props act. HH.HTML props act
paginationView = do
HH.nav [classes_ [B.pagination,B.isRounded]] [
HH.nav [classes_ [B.pagination, B.isRounded, B.pt4]
, HP.attr (HC.AttrName "area-label") "pagination"
, HP.attr (HC.AttrName "role") "navigation"
] [
HH.a [class_ B.paginationPrevious] [HH.text "Previous"]
, HH.a [class_ B.paginationNext] [HH.text "Next"]
, HH.ul [class_ B.paginationList] [
HH.li_ [HH.a [class_ B.paginationLink, HP.attr (HC.AttrName "area-label") "Go to page 1"] [HH.text "1"]]
, HH.li_ [HH.span [class_ B.paginationEllipsis] [HH.text "&hellip;"]]
, HH.li_ [HH.span [class_ B.paginationEllipsis] [HH.text "..."]]
, HH.li_ [HH.a [class_ B.paginationLink, HP.attr (HC.AttrName "area-label") "Go to page 45"] [HH.text "45"]]
, HH.li_ [HH.a [classes_ [B.paginationLink,B.isCurrent]
, HP.attr (HC.AttrName "area-label") "Go to page 46"] [HH.text "46"]]
, HH.li_ [HH.a [class_ B.paginationLink, HP.attr (HC.AttrName "area-label") "Go to page 1"] [HH.text "47"]]
, HH.li_ [HH.span [class_ B.paginationEllipsis] [HH.text "&hellip;"]]
, HH.li_ [HH.span [class_ B.paginationEllipsis] [HH.text "..."]]
, HH.li_ [HH.a [class_ B.paginationLink, HP.attr (HC.AttrName "area-label") "Go to page 45"] [HH.text "86"]]
]
]
]
81 changes: 80 additions & 1 deletion haskread-platform-ui/src/Page/Login.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,22 +2,42 @@ module Page.Login where

import Prelude

import Bulma.CSS.Spacing (pt4, py6)
import Bulma.Columns (column, columns, isHalf)
import Bulma.Common (isFullwidth)
import Bulma.Elements.Button (button)
import Bulma.Elements.Elements (box)
import Bulma.Form.General (IconAlignment(..)) as Bulma
import Bulma.Form.General (IconAlignment, control, field, hasIconAlignment, isCentered, label)
import Bulma.Form.Input (input)
import Bulma.Modifiers.Helpers (isPrimary)
import Bulma.Modifiers.Typography (hasTextCentered, hasTextWeightSemiBold, isSize4)
import Capability.Resource (class ManageUser, loginUser, class Navigate, navigate)
import Common.Types (MyRoute(..))
import Common.Utils (defaultPagination, safeHref, whenElem)
import Component.Footer as Footer
import Component.Header as Header
import Data.Either (Either(..), isLeft)
import Data.Maybe (Maybe(..))
import Effect.Aff.Class (class MonadAff)
import Effect.Class.Console (log)
import Halogen as H
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.HTML.Properties (classes)
import Halogen.HTML.Properties as HP
import Halogen.Store.Monad (class MonadStore)
import Store as Store
import Type.Proxy (Proxy(..))
import Utils.Bulma (class_, classes_)
import Web.Event.Event (Event)
import Web.Event.Event as Event

type Input = { redirect :: Boolean }

type OpaqueSlot slot = forall query. H.Slot query Void slot
type ChildSlots = (header :: OpaqueSlot Unit, footer :: OpaqueSlot Unit, communityList :: OpaqueSlot Unit, threadView :: OpaqueSlot Unit)

data Action
= SetEmail String
| SetPassword String
Expand All @@ -40,6 +60,7 @@ component
. MonadAff m
=> Navigate m
=> ManageUser m
=> MonadStore Store.Action Store.Store m
=> H.Component query Input output m
component = H.mkComponent
{ initialState
Expand Down Expand Up @@ -77,8 +98,64 @@ component = H.mkComponent
Nothing -> pure unit
Just _ -> navigate (Home defaultPagination)

render :: State -> H.ComponentHTML Action () m
render :: State -> H.ComponentHTML Action ChildSlots m
render st =
HH.div_
[ HH.slot_ (Proxy :: _ "header") unit Header.component unit
, HH.div [ classes_ [ columns, isCentered, py6 ] ]
[ HH.div [ classes_ [ column, isHalf ] ]
[ HH.div [ class_ box ]
[ HH.p [ classes_ [ isSize4, hasTextCentered, hasTextWeightSemiBold ] ] [ HH.text "Login to Haskread" ]
, HH.form [ HE.onSubmit HandleSubmit ]
[ whenElem (isLeft st.loginError) \_ ->
HH.div
[]
[ HH.text "Email or password is invalid" ]
, HH.div [ class_ field ]
[ HH.label [ class_ label ] [ HH.text "Email" ]
, HH.div [ classes_ [ control, hasIconAlignment Bulma.IconLeft ] ]
[ HH.input
[ class_ input
, HP.type_ HP.InputText
, HP.placeholder "Enter your email"
, HE.onValueInput SetEmail
, HP.value st.email
]
, HH.span [ HP.class_ $ HH.ClassName "icon is-small is-left" ]
[ HH.i [ HP.class_ $ HH.ClassName "bx bx-envelope" ] []
]
]
]
, HH.div [ class_ field ]
[ HH.label [ class_ label ] [ HH.text "Password" ]
, HH.div [ classes_ [ control, hasIconAlignment Bulma.IconLeft ] ]
[ HH.input
[ class_ input
, HP.type_ HP.InputPassword
, HP.placeholder "Enter your password"
, HE.onValueInput SetPassword
, HP.value st.password
]
, HH.span [ HP.class_ $ HH.ClassName "icon is-small is-left" ]
[ HH.i [ HP.class_ $ HH.ClassName "bx bx-lock" ] []
]
]
]
, HH.div [ class_ field ]
[ HH.div [ class_ control ]
[ HH.button [ classes_ [ button, isPrimary, isFullwidth ] ]
[ HH.strong_ [ HH.text "Login" ]
]
]
]
]
, HH.p [ classes_ [ hasTextCentered, pt4 ] ] [ HH.text "Don't have an account?", HH.a [ HP.href "/signup" ] [ HH.text "sign up" ] ]
]
]
]
, HH.slot_ (Proxy :: _ "footer") unit Footer.component unit
]
{-
HH.div_
[ HH.h1
[]
Expand Down Expand Up @@ -114,3 +191,5 @@ component = H.mkComponent
]
]
]
-}
2 changes: 1 addition & 1 deletion haskread-platform-ui/src/Store.purs
Original file line number Diff line number Diff line change
Expand Up @@ -17,4 +17,4 @@ data Action
reduce :: Store -> Action -> Store
reduce store = case _ of
LoginUser profile -> store { currentUser = Just profile }
LogoutUser -> store { currentUser = Nothing }
LogoutUser -> store { currentUser = Nothing }

0 comments on commit e59fd61

Please sign in to comment.